Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell98 |
Synopsis
- data OMap k v
- empty :: OMap k v
- singleton :: (k, v) -> OMap k v
- (<|) :: Ord k => (,) k v -> OMap k v -> OMap k v
- (|<) :: Ord k => (,) k v -> OMap k v -> OMap k v
- (>|) :: Ord k => OMap k v -> (,) k v -> OMap k v
- (|>) :: Ord k => OMap k v -> (,) k v -> OMap k v
- (<>|) :: Ord k => OMap k v -> OMap k v -> OMap k v
- (|<>) :: Ord k => OMap k v -> OMap k v -> OMap k v
- unionWithL :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v
- unionWithR :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v
- newtype Bias (dir :: IndexPreference) a = Bias {
- unbiased :: a
- type L = 'L
- type R = 'R
- delete :: Ord k => k -> OMap k v -> OMap k v
- filter :: Ord k => (k -> v -> Bool) -> OMap k v -> OMap k v
- (\\) :: Ord k => OMap k v -> OMap k v' -> OMap k v
- (|/\) :: Ord k => OMap k v -> OMap k v' -> OMap k v
- (/\|) :: Ord k => OMap k v -> OMap k v' -> OMap k v
- intersectionWith :: Ord k => (k -> v -> v' -> v'') -> OMap k v -> OMap k v' -> OMap k v''
- alter :: Ord k => (Maybe v -> Maybe v) -> k -> OMap k v -> OMap k v
- null :: OMap k v -> Bool
- size :: OMap k v -> Int
- member :: Ord k => k -> OMap k v -> Bool
- notMember :: Ord k => k -> OMap k v -> Bool
- lookup :: Ord k => k -> OMap k v -> Maybe v
- type Index = Int
- findIndex :: Ord k => k -> OMap k v -> Maybe Index
- elemAt :: OMap k v -> Index -> Maybe (k, v)
- fromList :: Ord k => [(k, v)] -> OMap k v
- assocs :: OMap k v -> [(k, v)]
- toAscList :: OMap k v -> [(k, v)]
- toMap :: OMap k v -> Map k v
Documentation
Instances
Foldable (OMap k) Source # | Values are produced in insertion order, not key order. |
Defined in Data.Map.Ordered.Internal fold :: Monoid m => OMap k m -> m # foldMap :: Monoid m => (a -> m) -> OMap k a -> m # foldMap' :: Monoid m => (a -> m) -> OMap k a -> m # foldr :: (a -> b -> b) -> b -> OMap k a -> b # foldr' :: (a -> b -> b) -> b -> OMap k a -> b # foldl :: (b -> a -> b) -> b -> OMap k a -> b # foldl' :: (b -> a -> b) -> b -> OMap k a -> b # foldr1 :: (a -> a -> a) -> OMap k a -> a # foldl1 :: (a -> a -> a) -> OMap k a -> a # elem :: Eq a => a -> OMap k a -> Bool # maximum :: Ord a => OMap k a -> a # minimum :: Ord a => OMap k a -> a # | |
Ord k => Traversable (OMap k) Source # | Values are traversed in insertion order, not key order. O(n*log(n)) where n is the size of the map. Since: 0.2 |
Functor (OMap k) Source # | Since: 0.2 |
(Data k, Data a, Ord k) => Data (OMap k a) Source # | Since: 0.2 |
Defined in Data.Map.Ordered.Internal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> OMap k a -> c (OMap k a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (OMap k a) # toConstr :: OMap k a -> Constr # dataTypeOf :: OMap k a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (OMap k a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (OMap k a)) # gmapT :: (forall b. Data b => b -> b) -> OMap k a -> OMap k a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> OMap k a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> OMap k a -> r # gmapQ :: (forall d. Data d => d -> u) -> OMap k a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> OMap k a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> OMap k a -> m (OMap k a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> OMap k a -> m (OMap k a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> OMap k a -> m (OMap k a) # | |
(Ord k, Monoid v) => Monoid (Bias L (OMap k v)) Source # | Empty maps and map union. When combining two sets that share elements, the
indices of the left argument are preferred, and the values are combined with
See the asymptotics of Since: 0.2 |
(Ord k, Monoid v) => Monoid (Bias R (OMap k v)) Source # | Empty maps and map union. When combining two sets that share elements, the
indices of the right argument are preferred, and the values are combined
with See the asymptotics of Since: 0.2 |
(Ord k, Semigroup v) => Semigroup (Bias L (OMap k v)) Source # | Since: 0.2 |
(Ord k, Semigroup v) => Semigroup (Bias R (OMap k v)) Source # | Since: 0.2 |
Ord k => IsList (OMap k v) Source # |
Since: 0.2.3 |
(Ord k, Read k, Read v) => Read (OMap k v) Source # | |
(Show k, Show v) => Show (OMap k v) Source # | |
(Eq k, Eq v) => Eq (OMap k v) Source # | |
(Ord k, Ord v) => Ord (OMap k v) Source # | |
Defined in Data.Map.Ordered.Internal | |
(Hashable k, Hashable v) => Hashable (OMap k v) Source # | Since: 0.2.3 |
Defined in Data.Map.Ordered.Internal | |
type Item (OMap k v) Source # | |
Defined in Data.Map.Ordered.Internal |
Trivial maps
Insertion
Conventions:
- The open side of an angle bracket points to an
OMap
- The pipe appears on the side whose indices take precedence if both sides contain the same key
- The left argument's indices are lower than the right argument's indices
- If both sides contain the same key, the tuple's value wins
(<>|) :: Ord k => OMap k v -> OMap k v -> OMap k v infixr 6 Source #
When a key occurs in both maps, prefer the value from the second map.
See asymptotics of unionWithR
.
(|<>) :: Ord k => OMap k v -> OMap k v -> OMap k v infixr 6 Source #
When a key occurs in both maps, prefer the value from the first map.
See asymptotics of unionWithL
.
unionWithL :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v Source #
Take the union. The first OMap
's argument's indices are lower than the
second. If a key appears in both maps, the first argument's index takes
precedence, and the supplied function is used to combine the values.
O(r*log(r)) where r is the size of the result
unionWithR :: Ord k => (k -> v -> v -> v) -> OMap k v -> OMap k v -> OMap k v Source #
Take the union. The first OMap
's argument's indices are lower than the
second. If a key appears in both maps, the second argument's index takes
precedence, and the supplied function is used to combine the values.
O(r*log(r)) where r is the size of the result
newtype Bias (dir :: IndexPreference) a Source #
A newtype to hang a Monoid
instance on. The phantom first parameter
tells whether mappend
will prefer the indices of its first or second
argument if there are shared elements in both.
Since: 0.2
Instances
Foldable (Bias dir) Source # | |
Defined in Data.Map.Util fold :: Monoid m => Bias dir m -> m # foldMap :: Monoid m => (a -> m) -> Bias dir a -> m # foldMap' :: Monoid m => (a -> m) -> Bias dir a -> m # foldr :: (a -> b -> b) -> b -> Bias dir a -> b # foldr' :: (a -> b -> b) -> b -> Bias dir a -> b # foldl :: (b -> a -> b) -> b -> Bias dir a -> b # foldl' :: (b -> a -> b) -> b -> Bias dir a -> b # foldr1 :: (a -> a -> a) -> Bias dir a -> a # foldl1 :: (a -> a -> a) -> Bias dir a -> a # elem :: Eq a => a -> Bias dir a -> Bool # maximum :: Ord a => Bias dir a -> a # minimum :: Ord a => Bias dir a -> a # | |
Traversable (Bias dir) Source # | |
Functor (Bias dir) Source # | |
(Typeable dir, Data a) => Data (Bias dir a) Source # | |
Defined in Data.Map.Util gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Bias dir a -> c (Bias dir a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Bias dir a) # toConstr :: Bias dir a -> Constr # dataTypeOf :: Bias dir a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Bias dir a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Bias dir a)) # gmapT :: (forall b. Data b => b -> b) -> Bias dir a -> Bias dir a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Bias dir a -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Bias dir a -> r # gmapQ :: (forall d. Data d => d -> u) -> Bias dir a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Bias dir a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Bias dir a -> m (Bias dir a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Bias dir a -> m (Bias dir a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Bias dir a -> m (Bias dir a) # | |
(Ord k, Monoid v) => Monoid (Bias L (OMap k v)) Source # | Empty maps and map union. When combining two sets that share elements, the
indices of the left argument are preferred, and the values are combined with
See the asymptotics of Since: 0.2 |
Ord a => Monoid (Bias L (OSet a)) Source # | Empty sets and set union. When combining two sets that share elements, the indices of the left argument are preferred. See the asymptotics of ( Since: 0.2 |
(Ord k, Monoid v) => Monoid (Bias R (OMap k v)) Source # | Empty maps and map union. When combining two sets that share elements, the
indices of the right argument are preferred, and the values are combined
with See the asymptotics of Since: 0.2 |
Ord a => Monoid (Bias R (OSet a)) Source # | Empty sets and set union. When combining two sets that share elements, the indices of the right argument are preferred. See the asymptotics of ( Since: 0.2 |
(Ord k, Semigroup v) => Semigroup (Bias L (OMap k v)) Source # | Since: 0.2 |
Ord a => Semigroup (Bias L (OSet a)) Source # | Since: 0.2 |
(Ord k, Semigroup v) => Semigroup (Bias R (OMap k v)) Source # | Since: 0.2 |
Ord a => Semigroup (Bias R (OSet a)) Source # | Since: 0.2 |
Read a => Read (Bias dir a) Source # | |
Show a => Show (Bias dir a) Source # | |
Eq a => Eq (Bias dir a) Source # | |
Ord a => Ord (Bias dir a) Source # | |
Deletion/Update
filter :: Ord k => (k -> v -> Bool) -> OMap k v -> OMap k v Source #
filter f m
contains exactly the key-value pairs of m
that satisfy f
,
without changing the order they appear
(\\) :: Ord k => OMap k v -> OMap k v' -> OMap k v Source #
m \\ n
deletes all the keys that exist in n
from m
O(m*log(n)) where m is the size of the smaller map and n is the size of the larger map.
(|/\) :: Ord k => OMap k v -> OMap k v' -> OMap k v Source #
Intersection. (The /\
is intended to look a bit like the standard
mathematical notation for set intersection.)
See asymptotics of intersectionWith
.
(/\|) :: Ord k => OMap k v -> OMap k v' -> OMap k v Source #
Intersection. (The /\
is intended to look a bit like the standard
mathematical notation for set intersection.)
See asymptotics of intersectionWith
.
intersectionWith :: Ord k => (k -> v -> v' -> v'') -> OMap k v -> OMap k v' -> OMap k v'' Source #
Take the intersection. The first OMap
's argument's indices are used for
the result.
O(m*log(n/(m+1)) + r*log(r)) where m is the size of the smaller map, n is the size of the larger map, and r is the size of the result.
alter :: Ord k => (Maybe v -> Maybe v) -> k -> OMap k v -> OMap k v Source #
Alter the value at k, or absence of. Can be used to insert delete or update
with the same semantics as Map
s alter
Query
Indexing
A 0-based index, much like the indices used by lists' !!
operation. All
indices are with respect to insertion order.
List conversions
fromList :: Ord k => [(k, v)] -> OMap k v Source #
If a key appears multiple times, the first occurrence is used for ordering and the last occurrence is used for its value. The library author welcomes comments on whether this default is sane.