Safe Haskell | Safe |
---|---|
Language | Haskell98 |
Synopsis
- class Foldable (m k) => Map m k where
- eqCmp :: m k a -> k -> k -> Bool
- empty :: m k a
- singleton :: k -> a -> m k a
- doubleton :: k -> a -> k -> a -> m k a
- null :: m k a -> Bool
- lookup :: k -> m k a -> Maybe a
- insertWith :: (a -> a -> a) -> k -> a -> m k a -> m k a
- insert :: k -> a -> m k a -> m k a
- update :: (a -> Maybe a) -> k -> m k a -> m k a
- adjust :: (a -> a) -> k -> m k a -> m k a
- delete :: k -> m k a -> m k a
- alter :: (Maybe a -> Maybe a) -> k -> m k a -> m k a
- unionWith :: (a -> a -> a) -> m k a -> m k a -> m k a
- differenceWith :: (a -> b -> Maybe a) -> m k a -> m k b -> m k a
- intersectionWith :: (a -> b -> c) -> m k a -> m k b -> m k c
- unionWithKey :: (k -> a -> a -> a) -> m k a -> m k a -> m k a
- differenceWithKey :: (k -> a -> b -> Maybe a) -> m k a -> m k b -> m k a
- intersectionWithKey :: (k -> a -> b -> c) -> m k a -> m k b -> m k c
- map :: (a -> b) -> m k a -> m k b
- mapWithKey :: (k -> a -> b) -> m k a -> m k b
- mapAccum :: (a -> b -> (a, c)) -> a -> m k b -> (a, m k c)
- mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> m k b -> (a, m k c)
- filter :: (a -> Bool) -> m k a -> m k a
- toListKV :: m k a -> [(k, a)]
- fromListKV :: [(k, a)] -> m k a
- fromListKVWith :: (a -> a -> a) -> [(k, a)] -> m k a
- serializeToList :: m k a -> [(k, a)]
- deserializeFromList :: [(k, a)] -> m k a
- isSubmapOfBy :: (a -> b -> Bool) -> m k a -> m k b -> Bool
- singletonView :: m k a -> Maybe (k, a)
- class Map m k => OrdMap m k where
- ordCmp :: m k a -> k -> k -> Ordering
- toAscList :: m k a -> [(k, a)]
- toDescList :: m k a -> [(k, a)]
- splitLookup :: k -> m k a -> (m k a, Maybe a, m k a)
- split :: k -> m k a -> (m k a, m k a)
- minViewWithKey :: m k a -> (Maybe (k, a), m k a)
- maxViewWithKey :: m k a -> (Maybe (k, a), m k a)
- findPredecessor :: k -> m k a -> Maybe (k, a)
- findSuccessor :: k -> m k a -> Maybe (k, a)
- mapAccumAsc :: (a -> b -> (a, c)) -> a -> m k b -> (a, m k c)
- mapAccumAscWithKey :: (a -> k -> b -> (a, c)) -> a -> m k b -> (a, m k c)
- mapAccumDesc :: (a -> b -> (a, c)) -> a -> m k b -> (a, m k c)
- mapAccumDescWithKey :: (a -> k -> b -> (a, c)) -> a -> m k b -> (a, m k c)
- data AList k v
- data WrappedIntMap k v
Documentation
class Foldable (m k) => Map m k where Source #
Minimal complete implementation:
eqCmp
Map
lookup
alter
unionWithKey
,differenceWithKey
,intersectionWithKey
toListKV
empty
orfromList
orfromListWith
isSubmapOfBy
For decent performance, supplying at least mapAccumWithKey
and filter
as
well is probably a good idea.
eqCmp, null, lookup, alter, unionWithKey, differenceWithKey, intersectionWithKey, toListKV, isSubmapOfBy
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 (==)
.
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 # | |
Defined in Data.ListTrie.Base.Map eqCmp :: Map k a -> k -> k -> Bool 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 # | |
Defined in Data.ListTrie.Base.Map 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 # | |
Defined in Data.ListTrie.Base.Map eqCmp :: AList k a -> k -> k -> Bool 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:
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
Instances
Ord k => OrdMap AList k Source # | |
Defined in Data.ListTrie.Base.Map 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 # | |
Defined in Data.ListTrie.Base.Map eqCmp :: AList k a -> k -> k -> Bool 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 # | |
Foldable (AList k) Source # | |
Defined in Data.ListTrie.Base.Map 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 # elem :: Eq a => a -> AList k a -> Bool # maximum :: Ord a => AList k a -> a # minimum :: Ord a => AList k a -> a # | |
Traversable (AList k) Source # | |
(Eq k, Eq v) => Eq (AList k v) Source # | |
(Ord k, Ord v) => Ord (AList k v) Source # | |
Defined in Data.ListTrie.Base.Map |
data WrappedIntMap k v Source #