list-tries-0.6.4: Tries and Patricia tries: finite sets and maps for list keys

Safe HaskellSafe
LanguageHaskell98

Data.ListTrie.Base.Map

Synopsis

Documentation

class Foldable (m k) => Map m k where Source #

Minimal complete implementation:

For decent performance, supplying at least mapAccumWithKey and filter as well is probably a good idea.

Methods

eqCmp :: m k a -> k -> k -> Bool Source #

Like an Eq instance over k, but should compare on the same type as m does. In most cases this can be defined just as const (==).

empty :: m k a Source #

singleton :: k -> a -> m k a Source #

doubleton :: k -> a -> k -> a -> m k a Source #

Precondition: the two keys differ

null :: m k a -> Bool Source #

lookup :: k -> m k a -> Maybe a Source #

insertWith :: (a -> a -> a) -> k -> a -> m k a -> m k a Source #

Strictness can be whatever is more optimal for the map type, shouldn't matter

insert :: k -> a -> m k a -> m k a Source #

update :: (a -> Maybe a) -> k -> m k a -> m k a Source #

adjust :: (a -> a) -> k -> m k a -> m k a Source #

delete :: k -> m k a -> m k a Source #

alter :: (Maybe a -> Maybe a) -> k -> m k a -> m k a Source #

unionWith :: (a -> a -> a) -> m k a -> m k a -> m k a Source #

differenceWith :: (a -> b -> Maybe a) -> m k a -> m k b -> m k a Source #

intersectionWith :: (a -> b -> c) -> m k a -> m k b -> m k c Source #

unionWithKey :: (k -> a -> a -> a) -> m k a -> m k a -> m k a Source #

differenceWithKey :: (k -> a -> b -> Maybe a) -> m k a -> m k b -> m k a Source #

intersectionWithKey :: (k -> a -> b -> c) -> m k a -> m k b -> m k c Source #

map :: (a -> b) -> m k a -> m k b Source #

mapWithKey :: (k -> a -> b) -> m k a -> m k b Source #

mapAccum :: (a -> b -> (a, c)) -> a -> m k b -> (a, m k c) Source #

mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> m k b -> (a, m k c) Source #

filter :: (a -> Bool) -> m k a -> m k a Source #

toListKV :: m k a -> [(k, a)] Source #

fromListKV :: [(k, a)] -> m k a Source #

fromListKVWith :: (a -> a -> a) -> [(k, a)] -> m k a Source #

serializeToList :: m k a -> [(k, a)] Source #

deserializeFromList :: [(k, a)] -> m k a Source #

isSubmapOfBy :: (a -> b -> Bool) -> m k a -> m k b -> Bool Source #

singletonView :: m k a -> Maybe (k, a) Source #

Instances

Ord k => Map Map k Source # 

Methods

eqCmp :: Map k a -> k -> k -> Bool Source #

empty :: Map k a Source #

singleton :: k -> a -> Map k a Source #

doubleton :: k -> a -> k -> a -> Map k a Source #

null :: Map k a -> Bool Source #

lookup :: k -> Map k a -> Maybe a Source #

insertWith :: (a -> a -> a) -> k -> a -> Map k a -> Map k a Source #

insert :: k -> a -> Map k a -> Map k a Source #

update :: (a -> Maybe a) -> k -> Map k a -> Map k a Source #

adjust :: (a -> a) -> k -> Map k a -> Map k a Source #

delete :: k -> Map k a -> Map k a Source #

alter :: (Maybe a -> Maybe a) -> k -> Map k a -> Map k a Source #

unionWith :: (a -> a -> a) -> Map k a -> Map k a -> Map k a Source #

differenceWith :: (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a Source #

intersectionWith :: (a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

unionWithKey :: (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a Source #

differenceWithKey :: (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a Source #

intersectionWithKey :: (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c Source #

map :: (a -> b) -> Map k a -> Map k b Source #

mapWithKey :: (k -> a -> b) -> Map k a -> Map k b Source #

mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #

mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #

filter :: (a -> Bool) -> Map k a -> Map k a Source #

toListKV :: Map k a -> [(k, a)] Source #

fromListKV :: [(k, a)] -> Map k a Source #

fromListKVWith :: (a -> a -> a) -> [(k, a)] -> Map k a Source #

serializeToList :: Map k a -> [(k, a)] Source #

deserializeFromList :: [(k, a)] -> Map k a Source #

isSubmapOfBy :: (a -> b -> Bool) -> Map k a -> Map k b -> Bool Source #

singletonView :: Map k a -> Maybe (k, a) Source #

Enum k => Map WrappedIntMap k Source # 

Methods

eqCmp :: WrappedIntMap k a -> k -> k -> Bool Source #

empty :: WrappedIntMap k a Source #

singleton :: k -> a -> WrappedIntMap k a Source #

doubleton :: k -> a -> k -> a -> WrappedIntMap k a Source #

null :: WrappedIntMap k a -> Bool Source #

lookup :: k -> WrappedIntMap k a -> Maybe a Source #

insertWith :: (a -> a -> a) -> k -> a -> WrappedIntMap k a -> WrappedIntMap k a Source #

insert :: k -> a -> WrappedIntMap k a -> WrappedIntMap k a Source #

update :: (a -> Maybe a) -> k -> WrappedIntMap k a -> WrappedIntMap k a Source #

adjust :: (a -> a) -> k -> WrappedIntMap k a -> WrappedIntMap k a Source #

delete :: k -> WrappedIntMap k a -> WrappedIntMap k a Source #

alter :: (Maybe a -> Maybe a) -> k -> WrappedIntMap k a -> WrappedIntMap k a Source #

unionWith :: (a -> a -> a) -> WrappedIntMap k a -> WrappedIntMap k a -> WrappedIntMap k a Source #

differenceWith :: (a -> b -> Maybe a) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k a Source #

intersectionWith :: (a -> b -> c) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k c Source #

unionWithKey :: (k -> a -> a -> a) -> WrappedIntMap k a -> WrappedIntMap k a -> WrappedIntMap k a Source #

differenceWithKey :: (k -> a -> b -> Maybe a) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k a Source #

intersectionWithKey :: (k -> a -> b -> c) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k c Source #

map :: (a -> b) -> WrappedIntMap k a -> WrappedIntMap k b Source #

mapWithKey :: (k -> a -> b) -> WrappedIntMap k a -> WrappedIntMap k b Source #

mapAccum :: (a -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

filter :: (a -> Bool) -> WrappedIntMap k a -> WrappedIntMap k a Source #

toListKV :: WrappedIntMap k a -> [(k, a)] Source #

fromListKV :: [(k, a)] -> WrappedIntMap k a Source #

fromListKVWith :: (a -> a -> a) -> [(k, a)] -> WrappedIntMap k a Source #

serializeToList :: WrappedIntMap k a -> [(k, a)] Source #

deserializeFromList :: [(k, a)] -> WrappedIntMap k a Source #

isSubmapOfBy :: (a -> b -> Bool) -> WrappedIntMap k a -> WrappedIntMap k b -> Bool Source #

singletonView :: WrappedIntMap k a -> Maybe (k, a) Source #

Eq k => Map AList k Source # 

Methods

eqCmp :: AList k a -> k -> k -> Bool Source #

empty :: AList k a Source #

singleton :: k -> a -> AList k a Source #

doubleton :: k -> a -> k -> a -> AList k a Source #

null :: AList k a -> Bool Source #

lookup :: k -> AList k a -> Maybe a Source #

insertWith :: (a -> a -> a) -> k -> a -> AList k a -> AList k a Source #

insert :: k -> a -> AList k a -> AList k a Source #

update :: (a -> Maybe a) -> k -> AList k a -> AList k a Source #

adjust :: (a -> a) -> k -> AList k a -> AList k a Source #

delete :: k -> AList k a -> AList k a Source #

alter :: (Maybe a -> Maybe a) -> k -> AList k a -> AList k a Source #

unionWith :: (a -> a -> a) -> AList k a -> AList k a -> AList k a Source #

differenceWith :: (a -> b -> Maybe a) -> AList k a -> AList k b -> AList k a Source #

intersectionWith :: (a -> b -> c) -> AList k a -> AList k b -> AList k c Source #

unionWithKey :: (k -> a -> a -> a) -> AList k a -> AList k a -> AList k a Source #

differenceWithKey :: (k -> a -> b -> Maybe a) -> AList k a -> AList k b -> AList k a Source #

intersectionWithKey :: (k -> a -> b -> c) -> AList k a -> AList k b -> AList k c Source #

map :: (a -> b) -> AList k a -> AList k b Source #

mapWithKey :: (k -> a -> b) -> AList k a -> AList k b Source #

mapAccum :: (a -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

filter :: (a -> Bool) -> AList k a -> AList k a Source #

toListKV :: AList k a -> [(k, a)] Source #

fromListKV :: [(k, a)] -> AList k a Source #

fromListKVWith :: (a -> a -> a) -> [(k, a)] -> AList k a Source #

serializeToList :: AList k a -> [(k, a)] Source #

deserializeFromList :: [(k, a)] -> AList k a Source #

isSubmapOfBy :: (a -> b -> Bool) -> AList k a -> AList k b -> Bool Source #

singletonView :: AList k a -> Maybe (k, a) Source #

class Map m k => OrdMap m k where Source #

Minimal complete definition:

For decent performance, supplying at least the following is probably a good idea:

Minimal complete definition

ordCmp, splitLookup

Methods

ordCmp :: m k a -> k -> k -> Ordering Source #

Like an Ord instance over k, but should compare on the same type as m does. In most cases this can be defined just as const compare.

toAscList :: m k a -> [(k, a)] Source #

toDescList :: m k a -> [(k, a)] Source #

splitLookup :: k -> m k a -> (m k a, Maybe a, m k a) Source #

split :: k -> m k a -> (m k a, m k a) Source #

minViewWithKey :: m k a -> (Maybe (k, a), m k a) Source #

maxViewWithKey :: m k a -> (Maybe (k, a), m k a) Source #

findPredecessor :: k -> m k a -> Maybe (k, a) Source #

findSuccessor :: k -> m k a -> Maybe (k, a) Source #

mapAccumAsc :: (a -> b -> (a, c)) -> a -> m k b -> (a, m k c) Source #

mapAccumAscWithKey :: (a -> k -> b -> (a, c)) -> a -> m k b -> (a, m k c) Source #

mapAccumDesc :: (a -> b -> (a, c)) -> a -> m k b -> (a, m k c) Source #

mapAccumDescWithKey :: (a -> k -> b -> (a, c)) -> a -> m k b -> (a, m k c) Source #

Instances

Ord k => OrdMap Map k Source # 

Methods

ordCmp :: Map k a -> k -> k -> Ordering Source #

toAscList :: Map k a -> [(k, a)] Source #

toDescList :: Map k a -> [(k, a)] Source #

splitLookup :: k -> Map k a -> (Map k a, Maybe a, Map k a) Source #

split :: k -> Map k a -> (Map k a, Map k a) Source #

minViewWithKey :: Map k a -> (Maybe (k, a), Map k a) Source #

maxViewWithKey :: Map k a -> (Maybe (k, a), Map k a) Source #

findPredecessor :: k -> Map k a -> Maybe (k, a) Source #

findSuccessor :: k -> Map k a -> Maybe (k, a) Source #

mapAccumAsc :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #

mapAccumAscWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #

mapAccumDesc :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #

mapAccumDescWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c) Source #

Enum k => OrdMap WrappedIntMap k Source # 

Methods

ordCmp :: WrappedIntMap k a -> k -> k -> Ordering Source #

toAscList :: WrappedIntMap k a -> [(k, a)] Source #

toDescList :: WrappedIntMap k a -> [(k, a)] Source #

splitLookup :: k -> WrappedIntMap k a -> (WrappedIntMap k a, Maybe a, WrappedIntMap k a) Source #

split :: k -> WrappedIntMap k a -> (WrappedIntMap k a, WrappedIntMap k a) Source #

minViewWithKey :: WrappedIntMap k a -> (Maybe (k, a), WrappedIntMap k a) Source #

maxViewWithKey :: WrappedIntMap k a -> (Maybe (k, a), WrappedIntMap k a) Source #

findPredecessor :: k -> WrappedIntMap k a -> Maybe (k, a) Source #

findSuccessor :: k -> WrappedIntMap k a -> Maybe (k, a) Source #

mapAccumAsc :: (a -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumAscWithKey :: (a -> k -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumDesc :: (a -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumDescWithKey :: (a -> k -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

Ord k => OrdMap AList k Source # 

Methods

ordCmp :: AList k a -> k -> k -> Ordering Source #

toAscList :: AList k a -> [(k, a)] Source #

toDescList :: AList k a -> [(k, a)] Source #

splitLookup :: k -> AList k a -> (AList k a, Maybe a, AList k a) Source #

split :: k -> AList k a -> (AList k a, AList k a) Source #

minViewWithKey :: AList k a -> (Maybe (k, a), AList k a) Source #

maxViewWithKey :: AList k a -> (Maybe (k, a), AList k a) Source #

findPredecessor :: k -> AList k a -> Maybe (k, a) Source #

findSuccessor :: k -> AList k a -> Maybe (k, a) Source #

mapAccumAsc :: (a -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumAscWithKey :: (a -> k -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumDesc :: (a -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumDescWithKey :: (a -> k -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

data AList k v Source #

Instances

Ord k => OrdMap AList k Source # 

Methods

ordCmp :: AList k a -> k -> k -> Ordering Source #

toAscList :: AList k a -> [(k, a)] Source #

toDescList :: AList k a -> [(k, a)] Source #

splitLookup :: k -> AList k a -> (AList k a, Maybe a, AList k a) Source #

split :: k -> AList k a -> (AList k a, AList k a) Source #

minViewWithKey :: AList k a -> (Maybe (k, a), AList k a) Source #

maxViewWithKey :: AList k a -> (Maybe (k, a), AList k a) Source #

findPredecessor :: k -> AList k a -> Maybe (k, a) Source #

findSuccessor :: k -> AList k a -> Maybe (k, a) Source #

mapAccumAsc :: (a -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumAscWithKey :: (a -> k -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumDesc :: (a -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumDescWithKey :: (a -> k -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

Eq k => Map AList k Source # 

Methods

eqCmp :: AList k a -> k -> k -> Bool Source #

empty :: AList k a Source #

singleton :: k -> a -> AList k a Source #

doubleton :: k -> a -> k -> a -> AList k a Source #

null :: AList k a -> Bool Source #

lookup :: k -> AList k a -> Maybe a Source #

insertWith :: (a -> a -> a) -> k -> a -> AList k a -> AList k a Source #

insert :: k -> a -> AList k a -> AList k a Source #

update :: (a -> Maybe a) -> k -> AList k a -> AList k a Source #

adjust :: (a -> a) -> k -> AList k a -> AList k a Source #

delete :: k -> AList k a -> AList k a Source #

alter :: (Maybe a -> Maybe a) -> k -> AList k a -> AList k a Source #

unionWith :: (a -> a -> a) -> AList k a -> AList k a -> AList k a Source #

differenceWith :: (a -> b -> Maybe a) -> AList k a -> AList k b -> AList k a Source #

intersectionWith :: (a -> b -> c) -> AList k a -> AList k b -> AList k c Source #

unionWithKey :: (k -> a -> a -> a) -> AList k a -> AList k a -> AList k a Source #

differenceWithKey :: (k -> a -> b -> Maybe a) -> AList k a -> AList k b -> AList k a Source #

intersectionWithKey :: (k -> a -> b -> c) -> AList k a -> AList k b -> AList k c Source #

map :: (a -> b) -> AList k a -> AList k b Source #

mapWithKey :: (k -> a -> b) -> AList k a -> AList k b Source #

mapAccum :: (a -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> AList k b -> (a, AList k c) Source #

filter :: (a -> Bool) -> AList k a -> AList k a Source #

toListKV :: AList k a -> [(k, a)] Source #

fromListKV :: [(k, a)] -> AList k a Source #

fromListKVWith :: (a -> a -> a) -> [(k, a)] -> AList k a Source #

serializeToList :: AList k a -> [(k, a)] Source #

deserializeFromList :: [(k, a)] -> AList k a Source #

isSubmapOfBy :: (a -> b -> Bool) -> AList k a -> AList k b -> Bool Source #

singletonView :: AList k a -> Maybe (k, a) Source #

Functor (AList k) Source # 

Methods

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

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

Foldable (AList k) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: AList k a -> Bool #

length :: AList k a -> Int #

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

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

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

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

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

Traversable (AList k) Source # 

Methods

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

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

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

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

(Eq k, Eq v) => Eq (AList k v) Source # 

Methods

(==) :: AList k v -> AList k v -> Bool #

(/=) :: AList k v -> AList k v -> Bool #

(Ord k, Ord v) => Ord (AList k v) Source # 

Methods

compare :: AList k v -> AList k v -> Ordering #

(<) :: AList k v -> AList k v -> Bool #

(<=) :: AList k v -> AList k v -> Bool #

(>) :: AList k v -> AList k v -> Bool #

(>=) :: AList k v -> AList k v -> Bool #

max :: AList k v -> AList k v -> AList k v #

min :: AList k v -> AList k v -> AList k v #

data WrappedIntMap k v Source #

Instances

Enum k => OrdMap WrappedIntMap k Source # 

Methods

ordCmp :: WrappedIntMap k a -> k -> k -> Ordering Source #

toAscList :: WrappedIntMap k a -> [(k, a)] Source #

toDescList :: WrappedIntMap k a -> [(k, a)] Source #

splitLookup :: k -> WrappedIntMap k a -> (WrappedIntMap k a, Maybe a, WrappedIntMap k a) Source #

split :: k -> WrappedIntMap k a -> (WrappedIntMap k a, WrappedIntMap k a) Source #

minViewWithKey :: WrappedIntMap k a -> (Maybe (k, a), WrappedIntMap k a) Source #

maxViewWithKey :: WrappedIntMap k a -> (Maybe (k, a), WrappedIntMap k a) Source #

findPredecessor :: k -> WrappedIntMap k a -> Maybe (k, a) Source #

findSuccessor :: k -> WrappedIntMap k a -> Maybe (k, a) Source #

mapAccumAsc :: (a -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumAscWithKey :: (a -> k -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumDesc :: (a -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumDescWithKey :: (a -> k -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

Enum k => Map WrappedIntMap k Source # 

Methods

eqCmp :: WrappedIntMap k a -> k -> k -> Bool Source #

empty :: WrappedIntMap k a Source #

singleton :: k -> a -> WrappedIntMap k a Source #

doubleton :: k -> a -> k -> a -> WrappedIntMap k a Source #

null :: WrappedIntMap k a -> Bool Source #

lookup :: k -> WrappedIntMap k a -> Maybe a Source #

insertWith :: (a -> a -> a) -> k -> a -> WrappedIntMap k a -> WrappedIntMap k a Source #

insert :: k -> a -> WrappedIntMap k a -> WrappedIntMap k a Source #

update :: (a -> Maybe a) -> k -> WrappedIntMap k a -> WrappedIntMap k a Source #

adjust :: (a -> a) -> k -> WrappedIntMap k a -> WrappedIntMap k a Source #

delete :: k -> WrappedIntMap k a -> WrappedIntMap k a Source #

alter :: (Maybe a -> Maybe a) -> k -> WrappedIntMap k a -> WrappedIntMap k a Source #

unionWith :: (a -> a -> a) -> WrappedIntMap k a -> WrappedIntMap k a -> WrappedIntMap k a Source #

differenceWith :: (a -> b -> Maybe a) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k a Source #

intersectionWith :: (a -> b -> c) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k c Source #

unionWithKey :: (k -> a -> a -> a) -> WrappedIntMap k a -> WrappedIntMap k a -> WrappedIntMap k a Source #

differenceWithKey :: (k -> a -> b -> Maybe a) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k a Source #

intersectionWithKey :: (k -> a -> b -> c) -> WrappedIntMap k a -> WrappedIntMap k b -> WrappedIntMap k c Source #

map :: (a -> b) -> WrappedIntMap k a -> WrappedIntMap k b Source #

mapWithKey :: (k -> a -> b) -> WrappedIntMap k a -> WrappedIntMap k b Source #

mapAccum :: (a -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> WrappedIntMap k b -> (a, WrappedIntMap k c) Source #

filter :: (a -> Bool) -> WrappedIntMap k a -> WrappedIntMap k a Source #

toListKV :: WrappedIntMap k a -> [(k, a)] Source #

fromListKV :: [(k, a)] -> WrappedIntMap k a Source #

fromListKVWith :: (a -> a -> a) -> [(k, a)] -> WrappedIntMap k a Source #

serializeToList :: WrappedIntMap k a -> [(k, a)] Source #

deserializeFromList :: [(k, a)] -> WrappedIntMap k a Source #

isSubmapOfBy :: (a -> b -> Bool) -> WrappedIntMap k a -> WrappedIntMap k b -> Bool Source #

singletonView :: WrappedIntMap k a -> Maybe (k, a) Source #

Functor (WrappedIntMap k) Source # 

Methods

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

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

Foldable (WrappedIntMap k) Source # 

Methods

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

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

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

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

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

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

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

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

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

null :: WrappedIntMap k a -> Bool #

length :: WrappedIntMap k a -> Int #

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

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

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

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

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

Traversable (WrappedIntMap k) Source # 

Methods

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

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

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

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

Eq v => Eq (WrappedIntMap k v) Source # 

Methods

(==) :: WrappedIntMap k v -> WrappedIntMap k v -> Bool #

(/=) :: WrappedIntMap k v -> WrappedIntMap k v -> Bool #

Ord v => Ord (WrappedIntMap k v) Source #