treemap-2.0.0.20161218: A tree of Data.Map.

Safe HaskellSafe
LanguageHaskell98

Data.TreeMap.Strict

Contents

Description

This module implements a strict TreeMap, which is like a Map but whose key is now a NonEmpty list of Map keys (a Path) enabling the possibility to gather mapped values by Path prefixes (inside a Node).

Synopsis

Documentation

Type TreeMap

newtype TreeMap k x Source #

Constructors

TreeMap (Map k (Node k x)) 

Instances

Ord k => Functor (TreeMap k) Source # 

Methods

fmap :: (a -> b) -> TreeMap k a -> TreeMap k b #

(<$) :: a -> TreeMap k b -> TreeMap k a #

Ord k => Foldable (TreeMap k) Source # 

Methods

fold :: Monoid m => TreeMap k m -> m #

foldMap :: Monoid m => (a -> m) -> TreeMap k a -> m #

foldr :: (a -> b -> b) -> b -> TreeMap k a -> b #

foldr' :: (a -> b -> b) -> b -> TreeMap k a -> b #

foldl :: (b -> a -> b) -> b -> TreeMap k a -> b #

foldl' :: (b -> a -> b) -> b -> TreeMap k a -> b #

foldr1 :: (a -> a -> a) -> TreeMap k a -> a #

foldl1 :: (a -> a -> a) -> TreeMap k a -> a #

toList :: TreeMap k a -> [a] #

null :: TreeMap k a -> Bool #

length :: TreeMap k a -> Int #

elem :: Eq a => a -> TreeMap k a -> Bool #

maximum :: Ord a => TreeMap k a -> a #

minimum :: Ord a => TreeMap k a -> a #

sum :: Num a => TreeMap k a -> a #

product :: Num a => TreeMap k a -> a #

Ord k => Traversable (TreeMap k) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> TreeMap k a -> f (TreeMap k b) #

sequenceA :: Applicative f => TreeMap k (f a) -> f (TreeMap k a) #

mapM :: Monad m => (a -> m b) -> TreeMap k a -> m (TreeMap k b) #

sequence :: Monad m => TreeMap k (m a) -> m (TreeMap k a) #

(Eq x, Eq k) => Eq (TreeMap k x) Source # 

Methods

(==) :: TreeMap k x -> TreeMap k x -> Bool #

(/=) :: TreeMap k x -> TreeMap k x -> Bool #

(Ord k, Data x, Data k) => Data (TreeMap k x) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TreeMap k x -> c (TreeMap k x) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (TreeMap k x) #

toConstr :: TreeMap k x -> Constr #

dataTypeOf :: TreeMap k x -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (TreeMap k x)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (TreeMap k x)) #

gmapT :: (forall b. Data b => b -> b) -> TreeMap k x -> TreeMap k x #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TreeMap k x -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TreeMap k x -> r #

gmapQ :: (forall d. Data d => d -> u) -> TreeMap k x -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TreeMap k x -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TreeMap k x -> m (TreeMap k x) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TreeMap k x -> m (TreeMap k x) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TreeMap k x -> m (TreeMap k x) #

(Show x, Show k) => Show (TreeMap k x) Source # 

Methods

showsPrec :: Int -> TreeMap k x -> ShowS #

show :: TreeMap k x -> String #

showList :: [TreeMap k x] -> ShowS #

(Ord k, Monoid v) => Monoid (TreeMap k v) Source # 

Methods

mempty :: TreeMap k v #

mappend :: TreeMap k v -> TreeMap k v -> TreeMap k v #

mconcat :: [TreeMap k v] -> TreeMap k v #

(Ord k, NFData k, NFData x) => NFData (TreeMap k x) Source # 

Methods

rnf :: TreeMap k x -> () #

Type Path

type Path = NonEmpty Source #

A Path is a non-empty list of Map keys.

path :: k -> [k] -> Path k Source #

list :: Path k -> [k] Source #

Type Node

data Node k x Source #

Constructors

Node 

Fields

Instances

Ord k => Functor (Node k) Source # 

Methods

fmap :: (a -> b) -> Node k a -> Node k b #

(<$) :: a -> Node k b -> Node k a #

Ord k => Foldable (Node k) Source # 

Methods

fold :: Monoid m => Node k m -> m #

foldMap :: Monoid m => (a -> m) -> Node k a -> m #

foldr :: (a -> b -> b) -> b -> Node k a -> b #

foldr' :: (a -> b -> b) -> b -> Node k a -> b #

foldl :: (b -> a -> b) -> b -> Node k a -> b #

foldl' :: (b -> a -> b) -> b -> Node k a -> b #

foldr1 :: (a -> a -> a) -> Node k a -> a #

foldl1 :: (a -> a -> a) -> Node k a -> a #

toList :: Node k a -> [a] #

null :: Node k a -> Bool #

length :: Node k a -> Int #

elem :: Eq a => a -> Node k a -> Bool #

maximum :: Ord a => Node k a -> a #

minimum :: Ord a => Node k a -> a #

sum :: Num a => Node k a -> a #

product :: Num a => Node k a -> a #

Ord k => Traversable (Node k) Source # 

Methods

traverse :: Applicative f => (a -> f b) -> Node k a -> f (Node k b) #

sequenceA :: Applicative f => Node k (f a) -> f (Node k a) #

mapM :: Monad m => (a -> m b) -> Node k a -> m (Node k b) #

sequence :: Monad m => Node k (m a) -> m (Node k a) #

(Eq k, Eq x) => Eq (Node k x) Source # 

Methods

(==) :: Node k x -> Node k x -> Bool #

(/=) :: Node k x -> Node k x -> Bool #

(Ord k, Data x, Data k) => Data (Node k x) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Node k x -> c (Node k x) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Node k x) #

toConstr :: Node k x -> Constr #

dataTypeOf :: Node k x -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Node k x)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Node k x)) #

gmapT :: (forall b. Data b => b -> b) -> Node k x -> Node k x #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Node k x -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Node k x -> r #

gmapQ :: (forall d. Data d => d -> u) -> Node k x -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Node k x -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Node k x -> m (Node k x) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Node k x -> m (Node k x) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Node k x -> m (Node k x) #

(Show k, Show x) => Show (Node k x) Source # 

Methods

showsPrec :: Int -> Node k x -> ShowS #

show :: Node k x -> String #

showList :: [Node k x] -> ShowS #

(Ord k, Monoid v) => Monoid (Node k v) Source # 

Methods

mempty :: Node k v #

mappend :: Node k v -> Node k v -> Node k v #

mconcat :: [Node k v] -> Node k v #

(Ord k, NFData k, NFData x) => NFData (Node k x) Source # 

Methods

rnf :: Node k x -> () #

node :: Maybe x -> TreeMap k x -> Node k x Source #

node_find :: Ord k => [k] -> Node k x -> Maybe (Node k x) Source #

Construct

empty :: TreeMap k x Source #

Return the empty TreeMap.

singleton :: Ord k => Path k -> x -> TreeMap k x Source #

Return a TreeMap only mapping the given Path to the given value.

leaf :: x -> Node k x Source #

Return a Node only containing the given value.

insert :: Ord k => (x -> x -> x) -> Path k -> x -> TreeMap k x -> TreeMap k x Source #

Return the given TreeMap associating the given Path with the given value, merging values if the given TreeMap already associates the given Path with a non-Nothing node_value.

from_List :: Ord k => (x -> x -> x) -> [(Path k, x)] -> TreeMap k x Source #

Return a TreeMap associating for each tuple of the given list the Path to the value, merging values of identical Paths (in respective order).

from_Map :: Ord k => (x -> x -> x) -> Map (Path k) x -> TreeMap k x Source #

Return a TreeMap associating for each key and value of the given Map the Path to the value, merging values of identical Paths (in respective order).

Size

nodes :: TreeMap k x -> Map k (Node k x) Source #

Return the Map in the given TreeMap.

null :: TreeMap k x -> Bool Source #

Return True iif. the given TreeMap is empty.

size :: TreeMap k x -> Int Source #

Return the number of non-Nothing node_values in the given TreeMap.

  • Complexity: O(r) where r is the size of the root Map.

Find

find :: Ord k => Path k -> TreeMap k x -> Maybe x Source #

Return the value (if any) associated with the given Path.

find_along :: Ord k => Path k -> TreeMap k x -> [x] Source #

Return the values (if any) associated with the prefixes of the given Path (included).

find_node :: Ord k => Path k -> TreeMap k x -> Maybe (Node k x) Source #

Return the Node (if any) associated with the given Path.

Union

union :: Ord k => (x -> x -> x) -> TreeMap k x -> TreeMap k x -> TreeMap k x Source #

Return a TreeMap associating the same Paths as both given TreeMaps, merging values (in respective order) when a Path leads to a non-Nothing node_value in both given TreeMaps.

unions :: Ord k => (x -> x -> x) -> [TreeMap k x] -> TreeMap k x Source #

Return the union of the given TreeMaps.

NOTE: use foldl' to reduce demand on the control-stack.

Map

map :: Ord k => (x -> y) -> TreeMap k x -> TreeMap k y Source #

Return the given TreeMap with each non-Nothing node_value mapped by the given function.

map_monotonic :: (Ord k, Ord l) => (k -> l) -> (x -> y) -> TreeMap k x -> TreeMap l y Source #

Return the given TreeMap with each Path section and each non-Nothing node_value mapped by the given functions.

WARNING: the function mapping Path sections must be monotonic, like in mapKeysMonotonic.

map_by_depth_first :: Ord k => (TreeMap k y -> Maybe x -> y) -> TreeMap k x -> TreeMap k y Source #

Return the given TreeMap with each node_value mapped by the given function supplied with the already mapped node_descendants of the current Node.

Alter

alterl_path :: Ord k => (Maybe x -> Maybe x) -> Path k -> TreeMap k x -> TreeMap k x Source #

Fold

foldl_with_Path :: Ord k => (a -> Path k -> x -> a) -> a -> TreeMap k x -> a Source #

Return the given accumulator folded by the given function applied on non-Nothing node_values from left to right through the given TreeMap.

foldl_with_Path_and_Node :: Ord k => (a -> Node k x -> Path k -> x -> a) -> a -> TreeMap k x -> a Source #

Return the given accumulator folded by the given function applied on non-Nothing Nodes and node_values from left to right through the given TreeMap.

foldr_with_Path :: Ord k => (Path k -> x -> a -> a) -> a -> TreeMap k x -> a Source #

Return the given accumulator folded by the given function applied on non-Nothing node_values from right to left through the given TreeMap.

foldr_with_Path_and_Node :: Ord k => (Node k x -> Path k -> x -> a -> a) -> a -> TreeMap k x -> a Source #

Return the given accumulator folded by the given function applied on non-Nothing Nodes and node_values from right to left through the given TreeMap.

foldl_path :: Ord k => (Path k -> x -> a -> a) -> Path k -> TreeMap k x -> a -> a Source #

Return the given accumulator folded by the given function applied on non-Nothing node_values from left to right along the given Path.

foldr_path :: Ord k => (Path k -> x -> a -> a) -> Path k -> TreeMap k x -> a -> a Source #

Return the given accumulator folded by the given function applied on non-Nothing node_values from right to left along the given Path.

Flatten

flatten :: Ord k => (x -> y) -> TreeMap k x -> Map (Path k) y Source #

Return a Map associating each Path leading to a non-Nothing node_value in the given TreeMap, with its value mapped by the given function.

flatten_with_Path :: Ord k => (Path k -> x -> y) -> TreeMap k x -> Map (Path k) y Source #

Like flatten but with also the current Path given to the mapping function.

Filter

filter :: Ord k => (x -> Bool) -> TreeMap k x -> TreeMap k x Source #

Return the given TreeMap keeping only its non-Nothing node_values passing the given predicate.

filter_with_Path :: Ord k => (Path k -> x -> Bool) -> TreeMap k x -> TreeMap k x Source #

Like filter but with also the current Path given to the predicate.

filter_with_Path_and_Node :: Ord k => (Node k x -> Path k -> x -> Bool) -> TreeMap k x -> TreeMap k x Source #

Like filter_with_Path but with also the current Node given to the predicate.

map_Maybe :: Ord k => (x -> Maybe y) -> TreeMap k x -> TreeMap k y Source #

Return the given TreeMap mapping its non-Nothing node_values and keeping only the non-Nothing results.

map_Maybe_with_Path :: Ord k => (Path k -> x -> Maybe y) -> TreeMap k x -> TreeMap k y Source #

Like map_Maybe but with also the current Path given to the predicate.

map_Maybe_with_Path_and_Node :: Ord k => (Node k x -> Path k -> x -> Maybe y) -> TreeMap k x -> TreeMap k y Source #

Like map_Maybe_with_Path but with also the current Node given to the predicate.

Orphan instances

Data x => Data (Maybe x) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Maybe x -> c (Maybe x) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Maybe x) #

toConstr :: Maybe x -> Constr #

dataTypeOf :: Maybe x -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Maybe x)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Maybe x)) #

gmapT :: (forall b. Data b => b -> b) -> Maybe x -> Maybe x #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Maybe x -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Maybe x -> r #

gmapQ :: (forall d. Data d => d -> u) -> Maybe x -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Maybe x -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Maybe x -> m (Maybe x) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe x -> m (Maybe x) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Maybe x -> m (Maybe x) #

Monoid x => Monoid (Maybe x) Source # 

Methods

mempty :: Maybe x #

mappend :: Maybe x -> Maybe x -> Maybe x #

mconcat :: [Maybe x] -> Maybe x #

NFData x => NFData (Maybe x) Source # 

Methods

rnf :: Maybe x -> () #