{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE ViewPatterns #-}
module Data.IntMap.NonEmpty (
NEIntMap
, Key
, pattern IsNonEmpty
, pattern IsEmpty
, nonEmptyMap
, toMap
, withNonEmpty
, insertMap
, insertMapWith
, insertMapWithKey
, insertMapMin
, insertMapMax
, unsafeFromMap
, singleton
, fromSet
, fromList
, fromListWith
, fromListWithKey
, fromAscList
, fromAscListWith
, fromAscListWithKey
, fromDistinctAscList
, insert
, insertWith
, insertWithKey
, insertLookupWithKey
, delete
, adjust
, adjustWithKey
, update
, updateWithKey
, updateLookupWithKey
, alter
, alterF
, alter'
, alterF'
, lookup
, (!?)
, (!)
, findWithDefault
, member
, notMember
, lookupLT
, lookupGT
, lookupLE
, lookupGE
, size
, union
, unionWith
, unionWithKey
, unions
, unionsWith
, difference
, (\\)
, differenceWith
, differenceWithKey
, intersection
, intersectionWith
, intersectionWithKey
, map
, mapWithKey
, traverseWithKey1
, traverseWithKey
, mapAccum
, mapAccumWithKey
, mapAccumRWithKey
, mapKeys
, mapKeysWith
, mapKeysMonotonic
, foldr
, foldl
, foldr1
, foldl1
, foldrWithKey
, foldlWithKey
, foldMapWithKey
, foldr'
, foldr1'
, foldl'
, foldl1'
, foldrWithKey'
, foldlWithKey'
, elems
, keys
, assocs
, keysSet
, toList
, toAscList
, toDescList
, filter
, filterWithKey
, restrictKeys
, withoutKeys
, partition
, partitionWithKey
, mapMaybe
, mapMaybeWithKey
, mapEither
, mapEitherWithKey
, split
, splitLookup
, splitRoot
, isSubmapOf, isSubmapOfBy
, isProperSubmapOf, isProperSubmapOfBy
, findMin
, findMax
, deleteMin
, deleteMax
, deleteFindMin
, deleteFindMax
, updateMin
, updateMax
, adjustMin
, adjustMax
, updateMinWithKey
, updateMaxWithKey
, adjustMinWithKey
, adjustMaxWithKey
, minView
, maxView
, valid
) where
import Control.Applicative
import Data.Bifunctor
import Data.Functor.Identity
import Data.IntMap.Internal (IntMap(..))
import Data.IntMap.NonEmpty.Internal
import Data.IntSet (IntSet)
import Data.IntSet.NonEmpty.Internal (NEIntSet(..))
import Data.List.NonEmpty (NonEmpty(..))
import Data.Maybe hiding (mapMaybe)
import Data.Semigroup.Foldable (Foldable1)
import Data.These
import Prelude hiding (map, filter, lookup, foldl, foldr, foldl1, foldr1)
import qualified Data.Foldable as F
import qualified Data.IntMap as M
import qualified Data.IntSet as S
import qualified Data.List.NonEmpty as NE
import qualified Data.Maybe as Maybe
import qualified Data.Semigroup.Foldable as F1
pattern IsNonEmpty :: NEIntMap a -> IntMap a
pattern $bIsNonEmpty :: NEIntMap a -> IntMap a
$mIsNonEmpty :: forall r a. IntMap a -> (NEIntMap a -> r) -> (Void# -> r) -> r
IsNonEmpty n <- (nonEmptyMap->Just n)
where
IsNonEmpty NEIntMap a
n = NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n
pattern IsEmpty :: IntMap a
pattern $bIsEmpty :: IntMap a
$mIsEmpty :: forall r a. IntMap a -> (Void# -> r) -> (Void# -> r) -> r
IsEmpty <- (M.null->True)
where
IsEmpty = IntMap a
forall a. IntMap a
M.empty
{-# COMPLETE IsNonEmpty, IsEmpty #-}
unsafeFromMap
:: IntMap a
-> NEIntMap a
unsafeFromMap :: IntMap a -> NEIntMap a
unsafeFromMap = NEIntMap a -> (NEIntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall r a. r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty NEIntMap a
forall a. a
e NEIntMap a -> NEIntMap a
forall a. a -> a
id
where
e :: a
e = [Char] -> a
forall a. [Char] -> a
errorWithoutStackTrace [Char]
"NEIntMap.unsafeFromMap: empty map"
{-# INLINE unsafeFromMap #-}
insertMap :: Key -> a -> IntMap a -> NEIntMap a
insertMap :: Key -> a -> IntMap a -> NEIntMap a
insertMap Key
k a
v = NEIntMap a -> (NEIntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall r a. r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v) (Key -> a -> NEIntMap a -> NEIntMap a
forall a. Key -> a -> NEIntMap a -> NEIntMap a
insert Key
k a
v)
{-# INLINE insertMap #-}
insertMapWith
:: (a -> a -> a)
-> Key
-> a
-> IntMap a
-> NEIntMap a
insertMapWith :: (a -> a -> a) -> Key -> a -> IntMap a -> NEIntMap a
insertMapWith a -> a -> a
f Key
k a
v = NEIntMap a -> (NEIntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall r a. r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v) ((a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
forall a. (a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
insertWith a -> a -> a
f Key
k a
v)
{-# INLINE insertMapWith #-}
insertMapWithKey
:: (Key -> a -> a -> a)
-> Key
-> a
-> IntMap a
-> NEIntMap a
insertMapWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> NEIntMap a
insertMapWithKey Key -> a -> a -> a
f Key
k a
v = NEIntMap a -> (NEIntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall r a. r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v) ((Key -> a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
forall a.
(Key -> a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
insertWithKey Key -> a -> a -> a
f Key
k a
v)
{-# INLINE insertMapWithKey #-}
insertMapMin
:: Key
-> a
-> IntMap a
-> NEIntMap a
insertMapMin :: Key -> a -> IntMap a -> NEIntMap a
insertMapMin = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap
{-# INLINE insertMapMin #-}
insertMapMax
:: Key
-> a
-> IntMap a
-> NEIntMap a
insertMapMax :: Key -> a -> IntMap a -> NEIntMap a
insertMapMax Key
k a
v = NEIntMap a -> (NEIntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall r a. r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v) NEIntMap a -> NEIntMap a
go
where
go :: NEIntMap a -> NEIntMap a
go (NEIntMap Key
k0 a
v0 IntMap a
m0) = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v0 (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMaxMap Key
k a
v (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m0
{-# INLINE insertMapMax #-}
fromSet
:: (Key -> a)
-> NEIntSet
-> NEIntMap a
fromSet :: (Key -> a) -> NEIntSet -> NEIntMap a
fromSet Key -> a
f (NEIntSet Key
k IntSet
ks) = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k (Key -> a
f Key
k) ((Key -> a) -> IntSet -> IntMap a
forall a. (Key -> a) -> IntSet -> IntMap a
M.fromSet Key -> a
f IntSet
ks)
{-# INLINE fromSet #-}
fromListWith
:: (a -> a -> a)
-> NonEmpty (Key, a)
-> NEIntMap a
fromListWith :: (a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromListWith a -> a -> a
f = (Key -> a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
forall a. (Key -> a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromListWithKey ((a -> a -> a) -> Key -> a -> a -> a
forall a b. a -> b -> a
const a -> a -> a
f)
{-# INLINE fromListWith #-}
fromListWithKey
:: (Key -> a -> a -> a)
-> NonEmpty (Key, a)
-> NEIntMap a
fromListWithKey :: (Key -> a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromListWithKey Key -> a -> a -> a
f ((Key
k0, a
v0) :| [(Key, a)]
xs) = (NEIntMap a -> (Key, a) -> NEIntMap a)
-> NEIntMap a -> [(Key, a)] -> NEIntMap a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' NEIntMap a -> (Key, a) -> NEIntMap a
go (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k0 a
v0) [(Key, a)]
xs
where
go :: NEIntMap a -> (Key, a) -> NEIntMap a
go NEIntMap a
m (Key
k, a
v) = (Key -> a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
forall a.
(Key -> a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
insertWithKey Key -> a -> a -> a
f Key
k a
v NEIntMap a
m
{-# INLINE go #-}
{-# INLINE fromListWithKey #-}
fromAscList
:: NonEmpty (Key, a)
-> NEIntMap a
fromAscList :: NonEmpty (Key, a) -> NEIntMap a
fromAscList = NonEmpty (Key, a) -> NEIntMap a
forall a. NonEmpty (Key, a) -> NEIntMap a
fromDistinctAscList (NonEmpty (Key, a) -> NEIntMap a)
-> (NonEmpty (Key, a) -> NonEmpty (Key, a))
-> NonEmpty (Key, a)
-> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (Key, a) -> NonEmpty (Key, a)
forall b. NonEmpty (Key, b) -> NonEmpty (Key, b)
combineEq
{-# INLINE fromAscList #-}
fromAscListWith
:: (a -> a -> a)
-> NonEmpty (Key, a)
-> NEIntMap a
fromAscListWith :: (a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromAscListWith a -> a -> a
f = (Key -> a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
forall a. (Key -> a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromAscListWithKey ((a -> a -> a) -> Key -> a -> a -> a
forall a b. a -> b -> a
const a -> a -> a
f)
{-# INLINE fromAscListWith #-}
fromAscListWithKey
:: (Key -> a -> a -> a)
-> NonEmpty (Key, a)
-> NEIntMap a
fromAscListWithKey :: (Key -> a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromAscListWithKey Key -> a -> a -> a
f = NonEmpty (Key, a) -> NEIntMap a
forall a. NonEmpty (Key, a) -> NEIntMap a
fromDistinctAscList (NonEmpty (Key, a) -> NEIntMap a)
-> (NonEmpty (Key, a) -> NonEmpty (Key, a))
-> NonEmpty (Key, a)
-> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> a -> a) -> NonEmpty (Key, a) -> NonEmpty (Key, a)
forall b.
(Key -> b -> b -> b) -> NonEmpty (Key, b) -> NonEmpty (Key, b)
combineEqWith Key -> a -> a -> a
f
{-# INLINE fromAscListWithKey #-}
fromDistinctAscList :: NonEmpty (Key, a) -> NEIntMap a
fromDistinctAscList :: NonEmpty (Key, a) -> NEIntMap a
fromDistinctAscList ((Key
k, a
v) :| [(Key, a)]
xs) = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k a
v
(IntMap a -> NEIntMap a)
-> ([(Key, a)] -> IntMap a) -> [(Key, a)] -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
M.fromDistinctAscList
([(Key, a)] -> NEIntMap a) -> [(Key, a)] -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ [(Key, a)]
xs
{-# INLINE fromDistinctAscList #-}
insert
:: Key
-> a
-> NEIntMap a
-> NEIntMap a
insert :: Key -> a -> NEIntMap a -> NEIntMap a
insert Key
k a
v n :: NEIntMap a
n@(NEIntMap Key
k0 a
v0 IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k a
v (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n
Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k a
v IntMap a
m
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v0 (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
M.insert Key
k a
v (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE insert #-}
insertWithKey
:: (Key -> a -> a -> a)
-> Key
-> a
-> NEIntMap a
-> NEIntMap a
insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
insertWithKey Key -> a -> a -> a
f Key
k a
v n :: NEIntMap a
n@(NEIntMap Key
k0 a
v0 IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k a
v (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n
Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k (Key -> a -> a -> a
f Key
k a
v a
v0) IntMap a
m
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v0 (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
M.insertWithKey Key -> a -> a -> a
f Key
k a
v IntMap a
m
{-# INLINE insertWithKey #-}
insertLookupWithKey
:: (Key -> a -> a -> a)
-> Key
-> a
-> NEIntMap a
-> (Maybe a, NEIntMap a)
insertLookupWithKey :: (Key -> a -> a -> a)
-> Key -> a -> NEIntMap a -> (Maybe a, NEIntMap a)
insertLookupWithKey Key -> a -> a -> a
f Key
k a
v n :: NEIntMap a
n@(NEIntMap Key
k0 a
v0 IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> (Maybe a
forall a. Maybe a
Nothing, Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k a
v (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n )
Ordering
EQ -> (a -> Maybe a
forall a. a -> Maybe a
Just a
v , Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k (Key -> a -> a -> a
f Key
k a
v a
v0) IntMap a
m )
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v0 (IntMap a -> NEIntMap a)
-> (Maybe a, IntMap a) -> (Maybe a, NEIntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a)
forall a.
(Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a)
M.insertLookupWithKey Key -> a -> a -> a
f Key
k a
v IntMap a
m
{-# INLINE insertLookupWithKey #-}
delete :: Key -> NEIntMap a -> IntMap a
delete :: Key -> NEIntMap a -> IntMap a
delete Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n
Ordering
EQ -> IntMap a
m
Ordering
GT -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0 a
v (IntMap a -> IntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> IntMap a
M.delete Key
k (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE delete #-}
adjust
:: (a -> a)
-> Key
-> NEIntMap a
-> NEIntMap a
adjust :: (a -> a) -> Key -> NEIntMap a -> NEIntMap a
adjust a -> a
f = (Key -> a -> a) -> Key -> NEIntMap a -> NEIntMap a
forall a. (Key -> a -> a) -> Key -> NEIntMap a -> NEIntMap a
adjustWithKey ((a -> a) -> Key -> a -> a
forall a b. a -> b -> a
const a -> a
f)
{-# INLINE adjust #-}
adjustWithKey
:: (Key -> a -> a)
-> Key
-> NEIntMap a
-> NEIntMap a
adjustWithKey :: (Key -> a -> a) -> Key -> NEIntMap a -> NEIntMap a
adjustWithKey Key -> a -> a
f Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> NEIntMap a
n
Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 (Key -> a -> a
f Key
k0 a
v) IntMap a
m
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> a) -> Key -> IntMap a -> IntMap a
M.adjustWithKey Key -> a -> a
f Key
k (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE adjustWithKey #-}
update
:: (a -> Maybe a)
-> Key
-> NEIntMap a
-> IntMap a
update :: (a -> Maybe a) -> Key -> NEIntMap a -> IntMap a
update a -> Maybe a
f = (Key -> a -> Maybe a) -> Key -> NEIntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> Key -> NEIntMap a -> IntMap a
updateWithKey ((a -> Maybe a) -> Key -> a -> Maybe a
forall a b. a -> b -> a
const a -> Maybe a
f)
{-# INLINE update #-}
updateWithKey
:: (Key -> a -> Maybe a)
-> Key
-> NEIntMap a
-> IntMap a
updateWithKey :: (Key -> a -> Maybe a) -> Key -> NEIntMap a -> IntMap a
updateWithKey Key -> a -> Maybe a
f Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n
Ordering
EQ -> IntMap a -> (a -> IntMap a) -> Maybe a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a
m ((a -> IntMap a -> IntMap a) -> IntMap a -> a -> IntMap a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0) IntMap a
m) (Maybe a -> IntMap a) -> (a -> Maybe a) -> a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> a -> Maybe a
f Key
k0 (a -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$ a
v
Ordering
GT -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0 a
v (IntMap a -> IntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
M.updateWithKey Key -> a -> Maybe a
f Key
k (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE updateWithKey #-}
updateLookupWithKey
:: (Key -> a -> Maybe a)
-> Key
-> NEIntMap a
-> (Maybe a, IntMap a)
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> NEIntMap a -> (Maybe a, IntMap a)
updateLookupWithKey Key -> a -> Maybe a
f Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> (Maybe a
forall a. Maybe a
Nothing, NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n)
Ordering
EQ -> let u :: Maybe a
u = Key -> a -> Maybe a
f Key
k0 a
v
in (a -> Maybe a
forall a. a -> Maybe a
Just a
v, IntMap a -> (a -> IntMap a) -> Maybe a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a
m ((a -> IntMap a -> IntMap a) -> IntMap a -> a -> IntMap a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0) IntMap a
m) Maybe a
u)
Ordering
GT -> (IntMap a -> IntMap a)
-> (Maybe a, IntMap a) -> (Maybe a, IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0 a
v) ((Maybe a, IntMap a) -> (Maybe a, IntMap a))
-> (IntMap a -> (Maybe a, IntMap a))
-> IntMap a
-> (Maybe a, IntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
forall a.
(Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
M.updateLookupWithKey Key -> a -> Maybe a
f Key
k (IntMap a -> (Maybe a, IntMap a))
-> IntMap a -> (Maybe a, IntMap a)
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE updateLookupWithKey #-}
alter
:: (Maybe a -> Maybe a)
-> Key
-> NEIntMap a
-> IntMap a
alter :: (Maybe a -> Maybe a) -> Key -> NEIntMap a -> IntMap a
alter Maybe a -> Maybe a
f Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> ((IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n) ((IntMap a -> IntMap a) -> IntMap a)
-> (Maybe a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a -> IntMap a)
-> (a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a -> IntMap a
forall a. a -> a
id (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k ) (Maybe a -> IntMap a) -> Maybe a -> IntMap a
forall a b. (a -> b) -> a -> b
$ Maybe a -> Maybe a
f Maybe a
forall a. Maybe a
Nothing
Ordering
EQ -> ((IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m ) ((IntMap a -> IntMap a) -> IntMap a)
-> (Maybe a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a -> IntMap a)
-> (a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a -> IntMap a
forall a. a -> a
id (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0) (Maybe a -> IntMap a) -> Maybe a -> IntMap a
forall a b. (a -> b) -> a -> b
$ Maybe a -> Maybe a
f (a -> Maybe a
forall a. a -> Maybe a
Just a
v)
Ordering
GT -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0 a
v (IntMap a -> IntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
M.alter Maybe a -> Maybe a
f Key
k (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE alter #-}
alterF
:: Functor f
=> (Maybe a -> f (Maybe a))
-> Key
-> NEIntMap a
-> f (IntMap a)
alterF :: (Maybe a -> f (Maybe a)) -> Key -> NEIntMap a -> f (IntMap a)
alterF Maybe a -> f (Maybe a)
f Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> ((IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n) ((IntMap a -> IntMap a) -> IntMap a)
-> (Maybe a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a -> IntMap a)
-> (a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a -> IntMap a
forall a. a -> a
id (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k ) (Maybe a -> IntMap a) -> f (Maybe a) -> f (IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a -> f (Maybe a)
f Maybe a
forall a. Maybe a
Nothing
Ordering
EQ -> ((IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m ) ((IntMap a -> IntMap a) -> IntMap a)
-> (Maybe a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a -> IntMap a)
-> (a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a -> IntMap a
forall a. a -> a
id (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0) (Maybe a -> IntMap a) -> f (Maybe a) -> f (IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a -> f (Maybe a)
f (a -> Maybe a
forall a. a -> Maybe a
Just a
v)
Ordering
GT -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k0 a
v (IntMap a -> IntMap a) -> f (IntMap a) -> f (IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a)
forall (f :: * -> *) a.
Functor f =>
(Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a)
M.alterF Maybe a -> f (Maybe a)
f Key
k IntMap a
m
{-# INLINABLE [2] alterF #-}
{-# RULES
"alterF/Const" forall k (f :: Maybe a -> Const b (Maybe a)) . alterF f k = \m -> Const . getConst . f $ lookup k m
#-}
{-# RULES
"alterF/Identity" forall k (f :: Maybe a -> Identity (Maybe a)) . alterF f k = Identity . alter (runIdentity . f) k
#-}
alter'
:: (Maybe a -> a)
-> Key
-> NEIntMap a
-> NEIntMap a
alter' :: (Maybe a -> a) -> Key -> NEIntMap a -> NEIntMap a
alter' Maybe a -> a
f Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k (Maybe a -> a
f Maybe a
forall a. Maybe a
Nothing) (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n
Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 (Maybe a -> a
f (a -> Maybe a
forall a. a -> Maybe a
Just a
v)) (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
M.alter (a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> (Maybe a -> a) -> Maybe a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe a -> a
f) Key
k (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE alter' #-}
alterF'
:: Functor f
=> (Maybe a -> f a)
-> Key
-> NEIntMap a
-> f (NEIntMap a)
alterF' :: (Maybe a -> f a) -> Key -> NEIntMap a -> f (NEIntMap a)
alterF' Maybe a -> f a
f Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> (a -> IntMap a -> NEIntMap a) -> IntMap a -> a -> NEIntMap a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k ) (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n) (a -> NEIntMap a) -> f a -> f (NEIntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a -> f a
f Maybe a
forall a. Maybe a
Nothing
Ordering
EQ -> (a -> IntMap a -> NEIntMap a) -> IntMap a -> a -> NEIntMap a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0) IntMap a
m (a -> NEIntMap a) -> f a -> f (NEIntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a -> f a
f (a -> Maybe a
forall a. a -> Maybe a
Just a
v)
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v (IntMap a -> NEIntMap a) -> f (IntMap a) -> f (NEIntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a)
forall (f :: * -> *) a.
Functor f =>
(Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a)
M.alterF ((a -> Maybe a) -> f a -> f (Maybe a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> Maybe a
forall a. a -> Maybe a
Just (f a -> f (Maybe a)) -> (Maybe a -> f a) -> Maybe a -> f (Maybe a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Maybe a -> f a
f) Key
k IntMap a
m
{-# INLINABLE [2] alterF' #-}
{-# RULES
"alterF'/Const" forall k (f :: Maybe a -> Const b a) . alterF' f k = \m -> Const . getConst . f $ lookup k m
#-}
{-# RULES
"alterF'/Identity" forall k (f :: Maybe a -> Identity a) . alterF' f k = Identity . insertWith (\_ -> runIdentity . f . Just) k (runIdentity (f Nothing))
#-}
lookup
:: Key
-> NEIntMap a
-> Maybe a
lookup :: Key -> NEIntMap a -> Maybe a
lookup Key
k (NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Maybe a
forall a. Maybe a
Nothing
Ordering
EQ -> a -> Maybe a
forall a. a -> Maybe a
Just a
v
Ordering
GT -> Key -> IntMap a -> Maybe a
forall a. Key -> IntMap a -> Maybe a
M.lookup Key
k IntMap a
m
{-# INLINE lookup #-}
(!?) :: NEIntMap a -> Key -> Maybe a
!? :: NEIntMap a -> Key -> Maybe a
(!?) = (Key -> NEIntMap a -> Maybe a) -> NEIntMap a -> Key -> Maybe a
forall a b c. (a -> b -> c) -> b -> a -> c
flip Key -> NEIntMap a -> Maybe a
forall a. Key -> NEIntMap a -> Maybe a
lookup
{-# INLINE (!?) #-}
(!) :: NEIntMap a -> Key -> a
(!) NEIntMap a
m Key
k = a -> Maybe a -> a
forall a. a -> Maybe a -> a
fromMaybe a
forall a. a
e (Maybe a -> a) -> Maybe a -> a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
m NEIntMap a -> Key -> Maybe a
forall a. NEIntMap a -> Key -> Maybe a
!? Key
k
where
e :: a
e = [Char] -> a
forall a. HasCallStack => [Char] -> a
error [Char]
"NEIntMap.!: given key is not an element in the map"
{-# INLINE (!) #-}
infixl 9 !?
infixl 9 !
findWithDefault
:: a
-> Key
-> NEIntMap a
-> a
findWithDefault :: a -> Key -> NEIntMap a -> a
findWithDefault a
def Key
k (NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> a
def
Ordering
EQ -> a
v
Ordering
GT -> a -> Key -> IntMap a -> a
forall a. a -> Key -> IntMap a -> a
M.findWithDefault a
def Key
k IntMap a
m
{-# INLINE findWithDefault #-}
member :: Key -> NEIntMap a -> Bool
member :: Key -> NEIntMap a -> Bool
member Key
k (NEIntMap Key
k0 a
_ IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Bool
False
Ordering
EQ -> Bool
True
Ordering
GT -> Key -> IntMap a -> Bool
forall a. Key -> IntMap a -> Bool
M.member Key
k IntMap a
m
{-# INLINE member #-}
notMember :: Key -> NEIntMap a -> Bool
notMember :: Key -> NEIntMap a -> Bool
notMember Key
k (NEIntMap Key
k0 a
_ IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Bool
True
Ordering
EQ -> Bool
False
Ordering
GT -> Key -> IntMap a -> Bool
forall a. Key -> IntMap a -> Bool
M.notMember Key
k IntMap a
m
{-# INLINE notMember #-}
lookupLT :: Key -> NEIntMap a -> Maybe (Key, a)
lookupLT :: Key -> NEIntMap a -> Maybe (Key, a)
lookupLT Key
k (NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Maybe (Key, a)
forall a. Maybe a
Nothing
Ordering
EQ -> Maybe (Key, a)
forall a. Maybe a
Nothing
Ordering
GT -> Key -> IntMap a -> Maybe (Key, a)
forall a. Key -> IntMap a -> Maybe (Key, a)
M.lookupLT Key
k IntMap a
m Maybe (Key, a) -> Maybe (Key, a) -> Maybe (Key, a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k0, a
v)
{-# INLINE lookupLT #-}
lookupGT :: Key -> NEIntMap a -> Maybe (Key, a)
lookupGT :: Key -> NEIntMap a -> Maybe (Key, a)
lookupGT Key
k (NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k0, a
v)
Ordering
EQ -> IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
lookupMinMap IntMap a
m
Ordering
GT -> Key -> IntMap a -> Maybe (Key, a)
forall a. Key -> IntMap a -> Maybe (Key, a)
M.lookupGT Key
k IntMap a
m
{-# INLINE lookupGT #-}
lookupLE :: Key -> NEIntMap a -> Maybe (Key, a)
lookupLE :: Key -> NEIntMap a -> Maybe (Key, a)
lookupLE Key
k (NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> Maybe (Key, a)
forall a. Maybe a
Nothing
Ordering
EQ -> (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k0, a
v)
Ordering
GT -> Key -> IntMap a -> Maybe (Key, a)
forall a. Key -> IntMap a -> Maybe (Key, a)
M.lookupLE Key
k IntMap a
m Maybe (Key, a) -> Maybe (Key, a) -> Maybe (Key, a)
forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k0, a
v)
{-# INLINE lookupLE #-}
lookupGE :: Key -> NEIntMap a -> Maybe (Key, a)
lookupGE :: Key -> NEIntMap a -> Maybe (Key, a)
lookupGE Key
k (NEIntMap Key
k0 a
v IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k0, a
v)
Ordering
EQ -> (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k0, a
v)
Ordering
GT -> Key -> IntMap a -> Maybe (Key, a)
forall a. Key -> IntMap a -> Maybe (Key, a)
M.lookupGE Key
k IntMap a
m
{-# INLINE lookupGE #-}
unionWith
:: (a -> a -> a)
-> NEIntMap a
-> NEIntMap a
-> NEIntMap a
unionWith :: (a -> a -> a) -> NEIntMap a -> NEIntMap a -> NEIntMap a
unionWith a -> a -> a
f n1 :: NEIntMap a
n1@(NEIntMap Key
k1 a
v1 IntMap a
m1) n2 :: NEIntMap a
n2@(NEIntMap Key
k2 a
v2 IntMap a
m2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k1 Key
k2 of
Ordering
LT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k1 a
v1 (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWith a -> a -> a
f IntMap a
m1 (IntMap a -> IntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n2
Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k1 (a -> a -> a
f a
v1 a
v2) (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWith a -> a -> a
f IntMap a
m1 (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m2
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k2 a
v2 (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWith a -> a -> a
f (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n1) (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m2
{-# INLINE unionWith #-}
unionWithKey
:: (Key -> a -> a -> a)
-> NEIntMap a
-> NEIntMap a
-> NEIntMap a
unionWithKey :: (Key -> a -> a -> a) -> NEIntMap a -> NEIntMap a -> NEIntMap a
unionWithKey Key -> a -> a -> a
f n1 :: NEIntMap a
n1@(NEIntMap Key
k1 a
v1 IntMap a
m1) n2 :: NEIntMap a
n2@(NEIntMap Key
k2 a
v2 IntMap a
m2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k1 Key
k2 of
Ordering
LT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k1 a
v1 (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWithKey Key -> a -> a -> a
f IntMap a
m1 (IntMap a -> IntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n2
Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k1 (Key -> a -> a -> a
f Key
k1 a
v1 a
v2) (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWithKey Key -> a -> a -> a
f IntMap a
m1 (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m2
Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k2 a
v2 (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWithKey Key -> a -> a -> a
f (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n1) (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m2
{-# INLINE unionWithKey #-}
unionsWith
:: Foldable1 f
=> (a -> a -> a)
-> f (NEIntMap a)
-> NEIntMap a
unionsWith :: (a -> a -> a) -> f (NEIntMap a) -> NEIntMap a
unionsWith a -> a -> a
f (f (NEIntMap a) -> NonEmpty (NEIntMap a)
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
F1.toNonEmpty->(NEIntMap a
m :| [NEIntMap a]
ms)) = (NEIntMap a -> NEIntMap a -> NEIntMap a)
-> NEIntMap a -> [NEIntMap a] -> NEIntMap a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' ((a -> a -> a) -> NEIntMap a -> NEIntMap a -> NEIntMap a
forall a. (a -> a -> a) -> NEIntMap a -> NEIntMap a -> NEIntMap a
unionWith a -> a -> a
f) NEIntMap a
m [NEIntMap a]
ms
{-# INLINE unionsWith #-}
difference
:: NEIntMap a
-> NEIntMap b
-> IntMap a
difference :: NEIntMap a -> NEIntMap b -> IntMap a
difference n1 :: NEIntMap a
n1@(NEIntMap Key
k1 a
v1 IntMap a
m1) n2 :: NEIntMap b
n2@(NEIntMap Key
k2 b
_ IntMap b
m2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k1 Key
k2 of
Ordering
LT -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k1 a
v1 (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m1 IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
`M.difference` NEIntMap b -> IntMap b
forall a. NEIntMap a -> IntMap a
toMap NEIntMap b
n2
Ordering
EQ -> IntMap a
m1 IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
`M.difference` IntMap b
m2
Ordering
GT -> NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n1 IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
`M.difference` IntMap b
m2
{-# INLINE difference #-}
(\\)
:: NEIntMap a
-> NEIntMap b
-> IntMap a
\\ :: NEIntMap a -> NEIntMap b -> IntMap a
(\\) = NEIntMap a -> NEIntMap b -> IntMap a
forall a b. NEIntMap a -> NEIntMap b -> IntMap a
difference
{-# INLINE (\\) #-}
differenceWith
:: (a -> b -> Maybe a)
-> NEIntMap a
-> NEIntMap b
-> IntMap a
differenceWith :: (a -> b -> Maybe a) -> NEIntMap a -> NEIntMap b -> IntMap a
differenceWith a -> b -> Maybe a
f = (Key -> a -> b -> Maybe a) -> NEIntMap a -> NEIntMap b -> IntMap a
forall a b.
(Key -> a -> b -> Maybe a) -> NEIntMap a -> NEIntMap b -> IntMap a
differenceWithKey ((a -> b -> Maybe a) -> Key -> a -> b -> Maybe a
forall a b. a -> b -> a
const a -> b -> Maybe a
f)
{-# INLINE differenceWith #-}
differenceWithKey
:: (Key -> a -> b -> Maybe a)
-> NEIntMap a
-> NEIntMap b
-> IntMap a
differenceWithKey :: (Key -> a -> b -> Maybe a) -> NEIntMap a -> NEIntMap b -> IntMap a
differenceWithKey Key -> a -> b -> Maybe a
f n1 :: NEIntMap a
n1@(NEIntMap Key
k1 a
v1 IntMap a
m1) n2 :: NEIntMap b
n2@(NEIntMap Key
k2 b
v2 IntMap b
m2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k1 Key
k2 of
Ordering
LT -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k1 a
v1 (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
forall a b.
(Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
M.differenceWithKey Key -> a -> b -> Maybe a
f IntMap a
m1 (NEIntMap b -> IntMap b
forall a. NEIntMap a -> IntMap a
toMap NEIntMap b
n2)
Ordering
EQ -> ((IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
forall a b.
(Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
M.differenceWithKey Key -> a -> b -> Maybe a
f IntMap a
m1 IntMap b
m2) ((IntMap a -> IntMap a) -> IntMap a)
-> (Maybe a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a -> IntMap a)
-> (a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a -> IntMap a
forall a. a -> a
id (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k1) (Maybe a -> IntMap a) -> Maybe a -> IntMap a
forall a b. (a -> b) -> a -> b
$ Key -> a -> b -> Maybe a
f Key
k1 a
v1 b
v2
Ordering
GT -> (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
forall a b.
(Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
M.differenceWithKey Key -> a -> b -> Maybe a
f (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n1) IntMap b
m2
{-# INLINE differenceWithKey #-}
intersection
:: NEIntMap a
-> NEIntMap b
-> IntMap a
intersection :: NEIntMap a -> NEIntMap b -> IntMap a
intersection n1 :: NEIntMap a
n1@(NEIntMap Key
k1 a
v1 IntMap a
m1) n2 :: NEIntMap b
n2@(NEIntMap Key
k2 b
_ IntMap b
m2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k1 Key
k2 of
Ordering
LT -> IntMap a
m1 IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
`M.intersection` NEIntMap b -> IntMap b
forall a. NEIntMap a -> IntMap a
toMap NEIntMap b
n2
Ordering
EQ -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k1 a
v1 (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m1 IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
`M.intersection` IntMap b
m2
Ordering
GT -> NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n1 IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
`M.intersection` IntMap b
m2
{-# INLINE intersection #-}
intersectionWith
:: (a -> b -> c)
-> NEIntMap a
-> NEIntMap b
-> IntMap c
intersectionWith :: (a -> b -> c) -> NEIntMap a -> NEIntMap b -> IntMap c
intersectionWith a -> b -> c
f = (Key -> a -> b -> c) -> NEIntMap a -> NEIntMap b -> IntMap c
forall a b c.
(Key -> a -> b -> c) -> NEIntMap a -> NEIntMap b -> IntMap c
intersectionWithKey ((a -> b -> c) -> Key -> a -> b -> c
forall a b. a -> b -> a
const a -> b -> c
f)
{-# INLINE intersectionWith #-}
intersectionWithKey
:: (Key -> a -> b -> c)
-> NEIntMap a
-> NEIntMap b
-> IntMap c
intersectionWithKey :: (Key -> a -> b -> c) -> NEIntMap a -> NEIntMap b -> IntMap c
intersectionWithKey Key -> a -> b -> c
f n1 :: NEIntMap a
n1@(NEIntMap Key
k1 a
v1 IntMap a
m1) n2 :: NEIntMap b
n2@(NEIntMap Key
k2 b
v2 IntMap b
m2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k1 Key
k2 of
Ordering
LT -> (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c.
(Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
M.intersectionWithKey Key -> a -> b -> c
f IntMap a
m1 (NEIntMap b -> IntMap b
forall a. NEIntMap a -> IntMap a
toMap NEIntMap b
n2)
Ordering
EQ -> Key -> c -> IntMap c -> IntMap c
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k1 (Key -> a -> b -> c
f Key
k1 a
v1 b
v2) (IntMap c -> IntMap c) -> IntMap c -> IntMap c
forall a b. (a -> b) -> a -> b
$ (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c.
(Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
M.intersectionWithKey Key -> a -> b -> c
f IntMap a
m1 IntMap b
m2
Ordering
GT -> (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c.
(Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
M.intersectionWithKey Key -> a -> b -> c
f (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n1) IntMap b
m2
{-# INLINE intersectionWithKey #-}
mapWithKey :: (Key -> a -> b) -> NEIntMap a -> NEIntMap b
mapWithKey :: (Key -> a -> b) -> NEIntMap a -> NEIntMap b
mapWithKey Key -> a -> b
f (NEIntMap Key
k a
v IntMap a
m) = Key -> b -> IntMap b -> NEIntMap b
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k (Key -> a -> b
f Key
k a
v) ((Key -> a -> b) -> IntMap a -> IntMap b
forall a b. (Key -> a -> b) -> IntMap a -> IntMap b
M.mapWithKey Key -> a -> b
f IntMap a
m)
{-# NOINLINE [1] mapWithKey #-}
{-# RULES
"mapWithKey/mapWithKey" forall f g xs . mapWithKey f (mapWithKey g xs) =
mapWithKey (\k a -> f k (g k a)) xs
"mapWithKey/map" forall f g xs . mapWithKey f (map g xs) =
mapWithKey (\k a -> f k (g a)) xs
"map/mapWithKey" forall f g xs . map f (mapWithKey g xs) =
mapWithKey (\k a -> f (g k a)) xs
#-}
mapAccum
:: (a -> b -> (a, c))
-> a
-> NEIntMap b
-> (a, NEIntMap c)
mapAccum :: (a -> b -> (a, c)) -> a -> NEIntMap b -> (a, NEIntMap c)
mapAccum a -> b -> (a, c)
f = (a -> Key -> b -> (a, c)) -> a -> NEIntMap b -> (a, NEIntMap c)
forall a b c.
(a -> Key -> b -> (a, c)) -> a -> NEIntMap b -> (a, NEIntMap c)
mapAccumWithKey (\a
x Key
_ -> a -> b -> (a, c)
f a
x)
{-# INLINE mapAccum #-}
mapAccumWithKey
:: (a -> Key -> b -> (a, c))
-> a
-> NEIntMap b
-> (a, NEIntMap c)
mapAccumWithKey :: (a -> Key -> b -> (a, c)) -> a -> NEIntMap b -> (a, NEIntMap c)
mapAccumWithKey a -> Key -> b -> (a, c)
f a
z0 (NEIntMap Key
k b
v IntMap b
m) = (a
z2, Key -> c -> IntMap c -> NEIntMap c
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k c
v' IntMap c
m')
where
~(a
z1, c
v') = a -> Key -> b -> (a, c)
f a
z0 Key
k b
v
~(a
z2, IntMap c
m') = (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
forall a b c.
(a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
M.mapAccumWithKey a -> Key -> b -> (a, c)
f a
z1 IntMap b
m
{-# INLINE mapAccumWithKey #-}
mapAccumRWithKey
:: (a -> Key -> b -> (a, c))
-> a
-> NEIntMap b
-> (a, NEIntMap c)
mapAccumRWithKey :: (a -> Key -> b -> (a, c)) -> a -> NEIntMap b -> (a, NEIntMap c)
mapAccumRWithKey a -> Key -> b -> (a, c)
f a
z0 (NEIntMap Key
k b
v IntMap b
m) = (a
z2, Key -> c -> IntMap c -> NEIntMap c
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k c
v' IntMap c
m')
where
~(a
z1, IntMap c
m') = (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
forall a b c.
(a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
M.mapAccumRWithKey a -> Key -> b -> (a, c)
f a
z0 IntMap b
m
~(a
z2, c
v') = a -> Key -> b -> (a, c)
f a
z1 Key
k b
v
{-# INLINE mapAccumRWithKey #-}
mapKeys
:: (Key -> Key)
-> NEIntMap a
-> NEIntMap a
mapKeys :: (Key -> Key) -> NEIntMap a -> NEIntMap a
mapKeys Key -> Key
f (NEIntMap Key
k0 a
v0 IntMap a
m) = (a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
forall a. (a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromListWith a -> a -> a
forall a b. a -> b -> a
const
(NonEmpty (Key, a) -> NEIntMap a)
-> (IntMap a -> NonEmpty (Key, a)) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key -> Key
f Key
k0, a
v0) (Key, a) -> [(Key, a)] -> NonEmpty (Key, a)
forall a. a -> [a] -> NonEmpty a
:|)
([(Key, a)] -> NonEmpty (Key, a))
-> (IntMap a -> [(Key, a)]) -> IntMap a -> NonEmpty (Key, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> [(Key, a)] -> [(Key, a)])
-> [(Key, a)] -> IntMap a -> [(Key, a)]
forall a b. (Key -> a -> b -> b) -> b -> IntMap a -> b
M.foldrWithKey (\Key
k a
v [(Key, a)]
kvs -> (Key -> Key
f Key
k, a
v) (Key, a) -> [(Key, a)] -> [(Key, a)]
forall a. a -> [a] -> [a]
: [(Key, a)]
kvs) []
(IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINABLE mapKeys #-}
mapKeysWith
:: (a -> a -> a)
-> (Key -> Key)
-> NEIntMap a
-> NEIntMap a
mapKeysWith :: (a -> a -> a) -> (Key -> Key) -> NEIntMap a -> NEIntMap a
mapKeysWith a -> a -> a
c Key -> Key
f (NEIntMap Key
k0 a
v0 IntMap a
m) = (a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
forall a. (a -> a -> a) -> NonEmpty (Key, a) -> NEIntMap a
fromListWith a -> a -> a
c
(NonEmpty (Key, a) -> NEIntMap a)
-> (IntMap a -> NonEmpty (Key, a)) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key -> Key
f Key
k0, a
v0) (Key, a) -> [(Key, a)] -> NonEmpty (Key, a)
forall a. a -> [a] -> NonEmpty a
:|)
([(Key, a)] -> NonEmpty (Key, a))
-> (IntMap a -> [(Key, a)]) -> IntMap a -> NonEmpty (Key, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> [(Key, a)] -> [(Key, a)])
-> [(Key, a)] -> IntMap a -> [(Key, a)]
forall a b. (Key -> a -> b -> b) -> b -> IntMap a -> b
M.foldrWithKey (\Key
k a
v [(Key, a)]
kvs -> (Key -> Key
f Key
k, a
v) (Key, a) -> [(Key, a)] -> [(Key, a)]
forall a. a -> [a] -> [a]
: [(Key, a)]
kvs) []
(IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINABLE mapKeysWith #-}
mapKeysMonotonic
:: (Key -> Key)
-> NEIntMap a
-> NEIntMap a
mapKeysMonotonic :: (Key -> Key) -> NEIntMap a -> NEIntMap a
mapKeysMonotonic Key -> Key
f (NEIntMap Key
k a
v IntMap a
m) = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap (Key -> Key
f Key
k) a
v
(IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> Key) -> IntMap a -> IntMap a
forall a. (Key -> Key) -> IntMap a -> IntMap a
M.mapKeysMonotonic Key -> Key
f
(IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE mapKeysMonotonic #-}
foldrWithKey :: (Key -> a -> b -> b) -> b -> NEIntMap a -> b
foldrWithKey :: (Key -> a -> b -> b) -> b -> NEIntMap a -> b
foldrWithKey Key -> a -> b -> b
f b
z (NEIntMap Key
k a
v IntMap a
m) = Key -> a -> b -> b
f Key
k a
v (b -> b) -> (IntMap a -> b) -> IntMap a -> b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> b -> b) -> b -> IntMap a -> b
forall a b. (Key -> a -> b -> b) -> b -> IntMap a -> b
M.foldrWithKey Key -> a -> b -> b
f b
z (IntMap a -> b) -> IntMap a -> b
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE foldrWithKey #-}
foldlWithKey :: (a -> Key -> b -> a) -> a -> NEIntMap b -> a
foldlWithKey :: (a -> Key -> b -> a) -> a -> NEIntMap b -> a
foldlWithKey a -> Key -> b -> a
f a
z (NEIntMap Key
k b
v IntMap b
m) = (a -> Key -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> Key -> b -> a) -> a -> IntMap b -> a
M.foldlWithKey a -> Key -> b -> a
f (a -> Key -> b -> a
f a
z Key
k b
v) IntMap b
m
{-# INLINE foldlWithKey #-}
foldr1' :: (a -> a -> a) -> NEIntMap a -> a
foldr1' :: (a -> a -> a) -> NEIntMap a -> a
foldr1' a -> a -> a
f (NEIntMap Key
_ a
v IntMap a
m) = case IntMap a -> Maybe (a, IntMap a)
forall a. IntMap a -> Maybe (a, IntMap a)
M.maxView IntMap a
m of
Maybe (a, IntMap a)
Nothing -> a
v
Just (a
y, IntMap a
m') -> let !z :: a
z = (a -> a -> a) -> a -> IntMap a -> a
forall a b. (a -> b -> b) -> b -> IntMap a -> b
M.foldr' a -> a -> a
f a
y IntMap a
m' in a
v a -> a -> a
`f` a
z
{-# INLINE foldr1' #-}
foldl1' :: (a -> a -> a) -> NEIntMap a -> a
foldl1' :: (a -> a -> a) -> NEIntMap a -> a
foldl1' a -> a -> a
f (NEIntMap Key
_ a
v IntMap a
m) = (a -> a -> a) -> a -> IntMap a -> a
forall a b. (a -> b -> a) -> a -> IntMap b -> a
M.foldl' a -> a -> a
f a
v IntMap a
m
{-# INLINE foldl1' #-}
foldrWithKey' :: (Key -> a -> b -> b) -> b -> NEIntMap a -> b
foldrWithKey' :: (Key -> a -> b -> b) -> b -> NEIntMap a -> b
foldrWithKey' Key -> a -> b -> b
f b
z (NEIntMap Key
k a
v IntMap a
m) = Key -> a -> b -> b
f Key
k a
v b
y
where
!y :: b
y = (Key -> a -> b -> b) -> b -> IntMap a -> b
forall a b. (Key -> a -> b -> b) -> b -> IntMap a -> b
M.foldrWithKey Key -> a -> b -> b
f b
z IntMap a
m
{-# INLINE foldrWithKey' #-}
foldlWithKey' :: (a -> Key -> b -> a) -> a -> NEIntMap b -> a
foldlWithKey' :: (a -> Key -> b -> a) -> a -> NEIntMap b -> a
foldlWithKey' a -> Key -> b -> a
f a
z (NEIntMap Key
k b
v IntMap b
m) = (a -> Key -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> Key -> b -> a) -> a -> IntMap b -> a
M.foldlWithKey' a -> Key -> b -> a
f a
x IntMap b
m
where
!x :: a
x = a -> Key -> b -> a
f a
z Key
k b
v
{-# INLINE foldlWithKey' #-}
keys :: NEIntMap a -> NonEmpty Key
keys :: NEIntMap a -> NonEmpty Key
keys (NEIntMap Key
k a
_ IntMap a
m) = Key
k Key -> [Key] -> NonEmpty Key
forall a. a -> [a] -> NonEmpty a
:| IntMap a -> [Key]
forall a. IntMap a -> [Key]
M.keys IntMap a
m
{-# INLINE keys #-}
assocs :: NEIntMap a -> NonEmpty (Key, a)
assocs :: NEIntMap a -> NonEmpty (Key, a)
assocs = NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
{-# INLINE assocs #-}
keysSet :: NEIntMap a -> NEIntSet
keysSet :: NEIntMap a -> NEIntSet
keysSet (NEIntMap Key
k a
_ IntMap a
m) = Key -> IntSet -> NEIntSet
NEIntSet Key
k (IntMap a -> IntSet
forall a. IntMap a -> IntSet
M.keysSet IntMap a
m)
{-# INLINE keysSet #-}
toAscList :: NEIntMap a -> NonEmpty (Key, a)
toAscList :: NEIntMap a -> NonEmpty (Key, a)
toAscList = NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
{-# INLINE toAscList #-}
toDescList :: NEIntMap a -> NonEmpty (Key, a)
toDescList :: NEIntMap a -> NonEmpty (Key, a)
toDescList (NEIntMap Key
k0 a
v0 IntMap a
m) = (NonEmpty (Key, a) -> Key -> a -> NonEmpty (Key, a))
-> NonEmpty (Key, a) -> IntMap a -> NonEmpty (Key, a)
forall a b. (a -> Key -> b -> a) -> a -> IntMap b -> a
M.foldlWithKey' NonEmpty (Key, a) -> Key -> a -> NonEmpty (Key, a)
forall a b. NonEmpty (a, b) -> a -> b -> NonEmpty (a, b)
go ((Key
k0, a
v0) (Key, a) -> [(Key, a)] -> NonEmpty (Key, a)
forall a. a -> [a] -> NonEmpty a
:| []) IntMap a
m
where
go :: NonEmpty (a, b) -> a -> b -> NonEmpty (a, b)
go NonEmpty (a, b)
xs a
k b
v = (a
k, b
v) (a, b) -> NonEmpty (a, b) -> NonEmpty (a, b)
forall a. a -> NonEmpty a -> NonEmpty a
NE.<| NonEmpty (a, b)
xs
{-# INLINE toDescList #-}
filter
:: (a -> Bool)
-> NEIntMap a
-> IntMap a
filter :: (a -> Bool) -> NEIntMap a -> IntMap a
filter a -> Bool
f (NEIntMap Key
k a
v IntMap a
m)
| a -> Bool
f a
v = Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v (IntMap a -> IntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> Bool) -> IntMap a -> IntMap a
forall a. (a -> Bool) -> IntMap a -> IntMap a
M.filter a -> Bool
f (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
| Bool
otherwise = (a -> Bool) -> IntMap a -> IntMap a
forall a. (a -> Bool) -> IntMap a -> IntMap a
M.filter a -> Bool
f IntMap a
m
{-# INLINE filter #-}
filterWithKey
:: (Key -> a -> Bool)
-> NEIntMap a
-> IntMap a
filterWithKey :: (Key -> a -> Bool) -> NEIntMap a -> IntMap a
filterWithKey Key -> a -> Bool
f (NEIntMap Key
k a
v IntMap a
m)
| Key -> a -> Bool
f Key
k a
v = Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v (IntMap a -> IntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> Bool) -> IntMap a -> IntMap a
forall a. (Key -> a -> Bool) -> IntMap a -> IntMap a
M.filterWithKey Key -> a -> Bool
f (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
| Bool
otherwise = (Key -> a -> Bool) -> IntMap a -> IntMap a
forall a. (Key -> a -> Bool) -> IntMap a -> IntMap a
M.filterWithKey Key -> a -> Bool
f IntMap a
m
{-# INLINE filterWithKey #-}
restrictKeys
:: NEIntMap a
-> IntSet
-> IntMap a
restrictKeys :: NEIntMap a -> IntSet -> IntMap a
restrictKeys n :: NEIntMap a
n@(NEIntMap Key
k a
v IntMap a
m) IntSet
xs = case IntSet -> Maybe (Key, IntSet)
S.minView IntSet
xs of
Maybe (Key, IntSet)
Nothing -> IntMap a
forall a. IntMap a
M.empty
Just (Key
y, IntSet
ys) -> case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
y of
Ordering
LT -> IntMap a
m IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
`M.restrictKeys` IntSet
xs
Ordering
EQ -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
`M.restrictKeys` IntSet
ys
Ordering
GT -> NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
`M.restrictKeys` IntSet
ys
{-# INLINE restrictKeys #-}
withoutKeys
:: NEIntMap a
-> IntSet
-> IntMap a
withoutKeys :: NEIntMap a -> IntSet -> IntMap a
withoutKeys n :: NEIntMap a
n@(NEIntMap Key
k a
v IntMap a
m) IntSet
xs = case IntSet -> Maybe (Key, IntSet)
S.minView IntSet
xs of
Maybe (Key, IntSet)
Nothing -> NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n
Just (Key
y, IntSet
ys) -> case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
y of
Ordering
LT -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
`M.withoutKeys` IntSet
xs
Ordering
EQ -> IntMap a
m IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
`M.withoutKeys` IntSet
ys
Ordering
GT -> NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
`M.withoutKeys` IntSet
ys
{-# INLINE withoutKeys #-}
partition
:: (a -> Bool)
-> NEIntMap a
-> These (NEIntMap a) (NEIntMap a)
partition :: (a -> Bool) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
partition a -> Bool
f = (Key -> a -> Bool) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a.
(Key -> a -> Bool) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
partitionWithKey ((a -> Bool) -> Key -> a -> Bool
forall a b. a -> b -> a
const a -> Bool
f)
{-# INLINE partition #-}
partitionWithKey
:: (Key -> a -> Bool)
-> NEIntMap a
-> These (NEIntMap a) (NEIntMap a)
partitionWithKey :: (Key -> a -> Bool) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
partitionWithKey Key -> a -> Bool
f n :: NEIntMap a
n@(NEIntMap Key
k a
v IntMap a
m0) = case (IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap a
m1, IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap a
m2) of
(Maybe (NEIntMap a)
Nothing, Maybe (NEIntMap a)
Nothing)
| Key -> a -> Bool
f Key
k a
v -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> These a b
This NEIntMap a
n
| Bool
otherwise -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. b -> These a b
That NEIntMap a
n
(Just NEIntMap a
n1, Maybe (NEIntMap a)
Nothing)
| Key -> a -> Bool
f Key
k a
v -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> These a b
This NEIntMap a
n
| Bool
otherwise -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These NEIntMap a
n1 (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v)
(Maybe (NEIntMap a)
Nothing, Just NEIntMap a
n2)
| Key -> a -> Bool
f Key
k a
v -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v) NEIntMap a
n2
| Bool
otherwise -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. b -> These a b
That NEIntMap a
n
(Just NEIntMap a
n1, Just NEIntMap a
n2)
| Key -> a -> Bool
f Key
k a
v -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k a
v IntMap a
m1) NEIntMap a
n2
| Bool
otherwise -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These NEIntMap a
n1 (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k a
v IntMap a
m2)
where
(IntMap a
m1, IntMap a
m2) = (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
forall a. (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
M.partitionWithKey Key -> a -> Bool
f IntMap a
m0
{-# INLINABLE partitionWithKey #-}
mapMaybe
:: (a -> Maybe b)
-> NEIntMap a
-> IntMap b
mapMaybe :: (a -> Maybe b) -> NEIntMap a -> IntMap b
mapMaybe a -> Maybe b
f = (Key -> a -> Maybe b) -> NEIntMap a -> IntMap b
forall a b. (Key -> a -> Maybe b) -> NEIntMap a -> IntMap b
mapMaybeWithKey ((a -> Maybe b) -> Key -> a -> Maybe b
forall a b. a -> b -> a
const a -> Maybe b
f)
{-# INLINE mapMaybe #-}
mapMaybeWithKey
:: (Key -> a -> Maybe b)
-> NEIntMap a
-> IntMap b
mapMaybeWithKey :: (Key -> a -> Maybe b) -> NEIntMap a -> IntMap b
mapMaybeWithKey Key -> a -> Maybe b
f (NEIntMap Key
k a
v IntMap a
m) = ((IntMap b -> IntMap b) -> IntMap b -> IntMap b
forall a b. (a -> b) -> a -> b
$ (Key -> a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (Key -> a -> Maybe b) -> IntMap a -> IntMap b
M.mapMaybeWithKey Key -> a -> Maybe b
f IntMap a
m)
((IntMap b -> IntMap b) -> IntMap b)
-> (Maybe b -> IntMap b -> IntMap b) -> Maybe b -> IntMap b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap b -> IntMap b)
-> (b -> IntMap b -> IntMap b) -> Maybe b -> IntMap b -> IntMap b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap b -> IntMap b
forall a. a -> a
id (Key -> b -> IntMap b -> IntMap b
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k)
(Maybe b -> IntMap b) -> Maybe b -> IntMap b
forall a b. (a -> b) -> a -> b
$ Key -> a -> Maybe b
f Key
k a
v
{-# INLINE mapMaybeWithKey #-}
mapEither
:: (a -> Either b c)
-> NEIntMap a
-> These (NEIntMap b) (NEIntMap c)
mapEither :: (a -> Either b c) -> NEIntMap a -> These (NEIntMap b) (NEIntMap c)
mapEither a -> Either b c
f = (Key -> a -> Either b c)
-> NEIntMap a -> These (NEIntMap b) (NEIntMap c)
forall a b c.
(Key -> a -> Either b c)
-> NEIntMap a -> These (NEIntMap b) (NEIntMap c)
mapEitherWithKey ((a -> Either b c) -> Key -> a -> Either b c
forall a b. a -> b -> a
const a -> Either b c
f)
{-# INLINE mapEither #-}
mapEitherWithKey
:: (Key -> a -> Either b c)
-> NEIntMap a
-> These (NEIntMap b) (NEIntMap c)
mapEitherWithKey :: (Key -> a -> Either b c)
-> NEIntMap a -> These (NEIntMap b) (NEIntMap c)
mapEitherWithKey Key -> a -> Either b c
f (NEIntMap Key
k a
v IntMap a
m0) = case (IntMap b -> Maybe (NEIntMap b)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap b
m1, IntMap c -> Maybe (NEIntMap c)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap c
m2) of
(Maybe (NEIntMap b)
Nothing, Maybe (NEIntMap c)
Nothing) -> case Key -> a -> Either b c
f Key
k a
v of
Left b
v' -> NEIntMap b -> These (NEIntMap b) (NEIntMap c)
forall a b. a -> These a b
This (Key -> b -> NEIntMap b
forall a. Key -> a -> NEIntMap a
singleton Key
k b
v')
Right c
v' -> NEIntMap c -> These (NEIntMap b) (NEIntMap c)
forall a b. b -> These a b
That (Key -> c -> NEIntMap c
forall a. Key -> a -> NEIntMap a
singleton Key
k c
v')
(Just NEIntMap b
n1, Maybe (NEIntMap c)
Nothing) -> case Key -> a -> Either b c
f Key
k a
v of
Left b
v' -> NEIntMap b -> These (NEIntMap b) (NEIntMap c)
forall a b. a -> These a b
This (Key -> b -> IntMap b -> NEIntMap b
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k b
v' IntMap b
m1)
Right c
v' -> NEIntMap b -> NEIntMap c -> These (NEIntMap b) (NEIntMap c)
forall a b. a -> b -> These a b
These NEIntMap b
n1 (Key -> c -> NEIntMap c
forall a. Key -> a -> NEIntMap a
singleton Key
k c
v')
(Maybe (NEIntMap b)
Nothing, Just NEIntMap c
n2) -> case Key -> a -> Either b c
f Key
k a
v of
Left b
v' -> NEIntMap b -> NEIntMap c -> These (NEIntMap b) (NEIntMap c)
forall a b. a -> b -> These a b
These (Key -> b -> NEIntMap b
forall a. Key -> a -> NEIntMap a
singleton Key
k b
v') NEIntMap c
n2
Right c
v' -> NEIntMap c -> These (NEIntMap b) (NEIntMap c)
forall a b. b -> These a b
That (Key -> c -> IntMap c -> NEIntMap c
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k c
v' IntMap c
m2)
(Just NEIntMap b
n1, Just NEIntMap c
n2) -> case Key -> a -> Either b c
f Key
k a
v of
Left b
v' -> NEIntMap b -> NEIntMap c -> These (NEIntMap b) (NEIntMap c)
forall a b. a -> b -> These a b
These (Key -> b -> IntMap b -> NEIntMap b
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k b
v' IntMap b
m1) NEIntMap c
n2
Right c
v' -> NEIntMap b -> NEIntMap c -> These (NEIntMap b) (NEIntMap c)
forall a b. a -> b -> These a b
These NEIntMap b
n1 (Key -> c -> IntMap c -> NEIntMap c
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k c
v' IntMap c
m2)
where
(IntMap b
m1, IntMap c
m2) = (Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
forall a b c.
(Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
M.mapEitherWithKey Key -> a -> Either b c
f IntMap a
m0
{-# INLINABLE mapEitherWithKey #-}
split
:: Key
-> NEIntMap a
-> Maybe (These (NEIntMap a) (NEIntMap a))
split :: Key -> NEIntMap a -> Maybe (These (NEIntMap a) (NEIntMap a))
split Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v IntMap a
m0) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> These (NEIntMap a) (NEIntMap a)
-> Maybe (These (NEIntMap a) (NEIntMap a))
forall a. a -> Maybe a
Just (These (NEIntMap a) (NEIntMap a)
-> Maybe (These (NEIntMap a) (NEIntMap a)))
-> These (NEIntMap a) (NEIntMap a)
-> Maybe (These (NEIntMap a) (NEIntMap a))
forall a b. (a -> b) -> a -> b
$ NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. b -> These a b
That NEIntMap a
n
Ordering
EQ -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. b -> These a b
That (NEIntMap a -> These (NEIntMap a) (NEIntMap a))
-> Maybe (NEIntMap a) -> Maybe (These (NEIntMap a) (NEIntMap a))
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap a
m0
Ordering
GT -> These (NEIntMap a) (NEIntMap a)
-> Maybe (These (NEIntMap a) (NEIntMap a))
forall a. a -> Maybe a
Just (These (NEIntMap a) (NEIntMap a)
-> Maybe (These (NEIntMap a) (NEIntMap a)))
-> These (NEIntMap a) (NEIntMap a)
-> Maybe (These (NEIntMap a) (NEIntMap a))
forall a b. (a -> b) -> a -> b
$ case (IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap a
m1, IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap a
m2) of
(Maybe (NEIntMap a)
Nothing, Maybe (NEIntMap a)
Nothing) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> These a b
This (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k0 a
v)
(Just NEIntMap a
_ , Maybe (NEIntMap a)
Nothing) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> These a b
This (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k0 a
v IntMap a
m1)
(Maybe (NEIntMap a)
Nothing, Just NEIntMap a
n2) -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k0 a
v) NEIntMap a
n2
(Just NEIntMap a
_ , Just NEIntMap a
n2) -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k0 a
v IntMap a
m1) NEIntMap a
n2
where
(IntMap a
m1, IntMap a
m2) = Key -> IntMap a -> (IntMap a, IntMap a)
forall a. Key -> IntMap a -> (IntMap a, IntMap a)
M.split Key
k IntMap a
m0
{-# INLINABLE split #-}
splitLookup
:: Key
-> NEIntMap a
-> These a (These (NEIntMap a) (NEIntMap a))
splitLookup :: Key -> NEIntMap a -> These a (These (NEIntMap a) (NEIntMap a))
splitLookup Key
k n :: NEIntMap a
n@(NEIntMap Key
k0 a
v0 IntMap a
m0) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
Ordering
LT -> These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a))
forall a b. b -> These a b
That (These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a)))
-> (NEIntMap a -> These (NEIntMap a) (NEIntMap a))
-> NEIntMap a
-> These a (These (NEIntMap a) (NEIntMap a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. b -> These a b
That (NEIntMap a -> These a (These (NEIntMap a) (NEIntMap a)))
-> NEIntMap a -> These a (These (NEIntMap a) (NEIntMap a))
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n
Ordering
EQ -> These a (These (NEIntMap a) (NEIntMap a))
-> (NEIntMap a -> These a (These (NEIntMap a) (NEIntMap a)))
-> Maybe (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (a -> These a (These (NEIntMap a) (NEIntMap a))
forall a b. a -> These a b
This a
v0) (a
-> These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a))
forall a b. a -> b -> These a b
These a
v0 (These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a)))
-> (NEIntMap a -> These (NEIntMap a) (NEIntMap a))
-> NEIntMap a
-> These a (These (NEIntMap a) (NEIntMap a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. b -> These a b
That) (Maybe (NEIntMap a) -> These a (These (NEIntMap a) (NEIntMap a)))
-> (IntMap a -> Maybe (NEIntMap a))
-> IntMap a
-> These a (These (NEIntMap a) (NEIntMap a))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap (IntMap a -> These a (These (NEIntMap a) (NEIntMap a)))
-> IntMap a -> These a (These (NEIntMap a) (NEIntMap a))
forall a b. (a -> b) -> a -> b
$ IntMap a
m0
Ordering
GT -> (These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a)))
-> (a
-> These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a)))
-> Maybe a
-> These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a))
forall b a. b -> (a -> b) -> Maybe a -> b
maybe These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a))
forall a b. b -> These a b
That a
-> These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a))
forall a b. a -> b -> These a b
These Maybe a
v (These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a)))
-> These (NEIntMap a) (NEIntMap a)
-> These a (These (NEIntMap a) (NEIntMap a))
forall a b. (a -> b) -> a -> b
$ case (IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap a
m1, IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap IntMap a
m2) of
(Maybe (NEIntMap a)
Nothing, Maybe (NEIntMap a)
Nothing) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> These a b
This (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k0 a
v0)
(Just NEIntMap a
_ , Maybe (NEIntMap a)
Nothing) -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> These a b
This (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k0 a
v0 IntMap a
m1)
(Maybe (NEIntMap a)
Nothing, Just NEIntMap a
n2) -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k0 a
v0) NEIntMap a
n2
(Just NEIntMap a
_ , Just NEIntMap a
n2) -> NEIntMap a -> NEIntMap a -> These (NEIntMap a) (NEIntMap a)
forall a b. a -> b -> These a b
These (Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k0 a
v0 IntMap a
m1) NEIntMap a
n2
where
(IntMap a
m1, Maybe a
v, IntMap a
m2) = Key -> IntMap a -> (IntMap a, Maybe a, IntMap a)
forall a. Key -> IntMap a -> (IntMap a, Maybe a, IntMap a)
M.splitLookup Key
k IntMap a
m0
{-# INLINABLE splitLookup #-}
splitRoot
:: NEIntMap a
-> NonEmpty (NEIntMap a)
splitRoot :: NEIntMap a -> NonEmpty (NEIntMap a)
splitRoot (NEIntMap Key
k a
v IntMap a
m) = Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v
NEIntMap a -> [NEIntMap a] -> NonEmpty (NEIntMap a)
forall a. a -> [a] -> NonEmpty a
:| (IntMap a -> Maybe (NEIntMap a)) -> [IntMap a] -> [NEIntMap a]
forall a b. (a -> Maybe b) -> [a] -> [b]
Maybe.mapMaybe IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap (IntMap a -> [IntMap a]
forall a. IntMap a -> [IntMap a]
M.splitRoot IntMap a
m)
{-# INLINE splitRoot #-}
isSubmapOf :: Eq a => NEIntMap a -> NEIntMap a -> Bool
isSubmapOf :: NEIntMap a -> NEIntMap a -> Bool
isSubmapOf = (a -> a -> Bool) -> NEIntMap a -> NEIntMap a -> Bool
forall a b. (a -> b -> Bool) -> NEIntMap a -> NEIntMap b -> Bool
isSubmapOfBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE isSubmapOf #-}
isSubmapOfBy
:: (a -> b -> Bool)
-> NEIntMap a
-> NEIntMap b
-> Bool
isSubmapOfBy :: (a -> b -> Bool) -> NEIntMap a -> NEIntMap b -> Bool
isSubmapOfBy a -> b -> Bool
f (NEIntMap Key
k a
v IntMap a
m0) (NEIntMap b -> IntMap b
forall a. NEIntMap a -> IntMap a
toMap->IntMap b
m1) = Bool
kvSub
Bool -> Bool -> Bool
&& (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
M.isSubmapOfBy a -> b -> Bool
f IntMap a
m0 IntMap b
m1
where
kvSub :: Bool
kvSub = case Key -> IntMap b -> Maybe b
forall a. Key -> IntMap a -> Maybe a
M.lookup Key
k IntMap b
m1 of
Just b
v0 -> a -> b -> Bool
f a
v b
v0
Maybe b
Nothing -> Bool
False
{-# INLINE isSubmapOfBy #-}
isProperSubmapOf :: Eq a => NEIntMap a -> NEIntMap a -> Bool
isProperSubmapOf :: NEIntMap a -> NEIntMap a -> Bool
isProperSubmapOf = (a -> a -> Bool) -> NEIntMap a -> NEIntMap a -> Bool
forall a b. (a -> b -> Bool) -> NEIntMap a -> NEIntMap b -> Bool
isProperSubmapOfBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==)
{-# INLINE isProperSubmapOf #-}
isProperSubmapOfBy
:: (a -> b -> Bool)
-> NEIntMap a
-> NEIntMap b
-> Bool
isProperSubmapOfBy :: (a -> b -> Bool) -> NEIntMap a -> NEIntMap b -> Bool
isProperSubmapOfBy a -> b -> Bool
f NEIntMap a
m1 NEIntMap b
m2 = IntMap a -> Key
forall a. IntMap a -> Key
M.size (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
neimIntMap NEIntMap a
m1) Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< IntMap b -> Key
forall a. IntMap a -> Key
M.size (NEIntMap b -> IntMap b
forall a. NEIntMap a -> IntMap a
neimIntMap NEIntMap b
m2)
Bool -> Bool -> Bool
&& (a -> b -> Bool) -> NEIntMap a -> NEIntMap b -> Bool
forall a b. (a -> b -> Bool) -> NEIntMap a -> NEIntMap b -> Bool
isSubmapOfBy a -> b -> Bool
f NEIntMap a
m1 NEIntMap b
m2
{-# INLINE isProperSubmapOfBy #-}
findMin :: NEIntMap a -> (Key, a)
findMin :: NEIntMap a -> (Key, a)
findMin (NEIntMap Key
k a
v IntMap a
_) = (Key
k, a
v)
{-# INLINE findMin #-}
findMax :: NEIntMap a -> (Key, a)
findMax :: NEIntMap a -> (Key, a)
findMax (NEIntMap Key
k a
v IntMap a
m) = (Key, a) -> Maybe (Key, a) -> (Key, a)
forall a. a -> Maybe a -> a
fromMaybe (Key
k, a
v) (Maybe (Key, a) -> (Key, a))
-> (IntMap a -> Maybe (Key, a)) -> IntMap a -> (Key, a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
lookupMaxMap (IntMap a -> (Key, a)) -> IntMap a -> (Key, a)
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE findMax #-}
deleteMin :: NEIntMap a -> IntMap a
deleteMin :: NEIntMap a -> IntMap a
deleteMin (NEIntMap Key
_ a
_ IntMap a
m) = IntMap a
m
{-# INLINE deleteMin #-}
deleteMax :: NEIntMap a -> IntMap a
deleteMax :: NEIntMap a -> IntMap a
deleteMax (NEIntMap Key
k a
v IntMap a
m) = case IntMap a -> Maybe (a, IntMap a)
forall a. IntMap a -> Maybe (a, IntMap a)
M.maxView IntMap a
m of
Maybe (a, IntMap a)
Nothing -> IntMap a
forall a. IntMap a
M.empty
Just (a
_, IntMap a
m') -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v IntMap a
m'
{-# INLINE deleteMax #-}
updateMin :: (a -> Maybe a) -> NEIntMap a -> IntMap a
updateMin :: (a -> Maybe a) -> NEIntMap a -> IntMap a
updateMin a -> Maybe a
f = (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
updateMinWithKey ((a -> Maybe a) -> Key -> a -> Maybe a
forall a b. a -> b -> a
const a -> Maybe a
f)
{-# INLINE updateMin #-}
adjustMin :: (a -> a) -> NEIntMap a -> NEIntMap a
adjustMin :: (a -> a) -> NEIntMap a -> NEIntMap a
adjustMin a -> a
f = (Key -> a -> a) -> NEIntMap a -> NEIntMap a
forall a. (Key -> a -> a) -> NEIntMap a -> NEIntMap a
adjustMinWithKey ((a -> a) -> Key -> a -> a
forall a b. a -> b -> a
const a -> a
f)
{-# INLINE adjustMin #-}
updateMinWithKey :: (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
updateMinWithKey :: (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
updateMinWithKey Key -> a -> Maybe a
f (NEIntMap Key
k a
v IntMap a
m) = ((IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m) ((IntMap a -> IntMap a) -> IntMap a)
-> (Maybe a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a -> IntMap a)
-> (a -> IntMap a -> IntMap a) -> Maybe a -> IntMap a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a -> IntMap a
forall a. a -> a
id (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k) (Maybe a -> IntMap a) -> Maybe a -> IntMap a
forall a b. (a -> b) -> a -> b
$ Key -> a -> Maybe a
f Key
k a
v
{-# INLINE updateMinWithKey #-}
adjustMinWithKey :: (Key -> a -> a) -> NEIntMap a -> NEIntMap a
adjustMinWithKey :: (Key -> a -> a) -> NEIntMap a -> NEIntMap a
adjustMinWithKey Key -> a -> a
f (NEIntMap Key
k a
v IntMap a
m) = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k (Key -> a -> a
f Key
k a
v) IntMap a
m
{-# INLINE adjustMinWithKey #-}
updateMax :: (a -> Maybe a) -> NEIntMap a -> IntMap a
updateMax :: (a -> Maybe a) -> NEIntMap a -> IntMap a
updateMax a -> Maybe a
f = (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
updateMaxWithKey ((a -> Maybe a) -> Key -> a -> Maybe a
forall a b. a -> b -> a
const a -> Maybe a
f)
{-# INLINE updateMax #-}
adjustMax :: (a -> a) -> NEIntMap a -> NEIntMap a
adjustMax :: (a -> a) -> NEIntMap a -> NEIntMap a
adjustMax a -> a
f = (Key -> a -> a) -> NEIntMap a -> NEIntMap a
forall a. (Key -> a -> a) -> NEIntMap a -> NEIntMap a
adjustMaxWithKey ((a -> a) -> Key -> a -> a
forall a b. a -> b -> a
const a -> a
f)
{-# INLINE adjustMax #-}
updateMaxWithKey :: (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
updateMaxWithKey :: (Key -> a -> Maybe a) -> NEIntMap a -> IntMap a
updateMaxWithKey Key -> a -> Maybe a
f (NEIntMap Key
k a
v IntMap a
m)
| IntMap a -> Bool
forall a. IntMap a -> Bool
M.null IntMap a
m = IntMap a -> (a -> IntMap a) -> Maybe a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a
m (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
M.singleton Key
k) (Maybe a -> IntMap a) -> Maybe a -> IntMap a
forall a b. (a -> b) -> a -> b
$ Key -> a -> Maybe a
f Key
k a
v
| Bool
otherwise = Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v
(IntMap a -> IntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
M.updateMaxWithKey Key -> a -> Maybe a
f
(IntMap a -> IntMap a) -> IntMap a -> IntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE updateMaxWithKey #-}
adjustMaxWithKey :: (Key -> a -> a) -> NEIntMap a -> NEIntMap a
adjustMaxWithKey :: (Key -> a -> a) -> NEIntMap a -> NEIntMap a
adjustMaxWithKey Key -> a -> a
f (NEIntMap Key
k0 a
v IntMap a
m)
| IntMap a -> Bool
forall a. IntMap a -> Bool
M.null IntMap a
m = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 (Key -> a -> a
f Key
k0 a
v) IntMap a
m
| Bool
otherwise = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
insertMapMin Key
k0 a
v
(IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
M.updateMaxWithKey (\Key
k -> a -> Maybe a
forall a. a -> Maybe a
Just (a -> Maybe a) -> (a -> a) -> a -> Maybe a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> a -> a
f Key
k)
(IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE adjustMaxWithKey #-}
minView :: NEIntMap a -> (a, IntMap a)
minView :: NEIntMap a -> (a, IntMap a)
minView = ((Key, a) -> a) -> ((Key, a), IntMap a) -> (a, IntMap a)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Key, a) -> a
forall a b. (a, b) -> b
snd (((Key, a), IntMap a) -> (a, IntMap a))
-> (NEIntMap a -> ((Key, a), IntMap a))
-> NEIntMap a
-> (a, IntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> ((Key, a), IntMap a)
forall a. NEIntMap a -> ((Key, a), IntMap a)
deleteFindMin
{-# INLINE minView #-}
deleteFindMin :: NEIntMap a -> ((Key, a), IntMap a)
deleteFindMin :: NEIntMap a -> ((Key, a), IntMap a)
deleteFindMin (NEIntMap Key
k a
v IntMap a
m) = ((Key
k, a
v), IntMap a
m)
{-# INLINE deleteFindMin #-}
maxView :: NEIntMap a -> (a, IntMap a)
maxView :: NEIntMap a -> (a, IntMap a)
maxView = ((Key, a) -> a) -> ((Key, a), IntMap a) -> (a, IntMap a)
forall (p :: * -> * -> *) a b c.
Bifunctor p =>
(a -> b) -> p a c -> p b c
first (Key, a) -> a
forall a b. (a, b) -> b
snd (((Key, a), IntMap a) -> (a, IntMap a))
-> (NEIntMap a -> ((Key, a), IntMap a))
-> NEIntMap a
-> (a, IntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> ((Key, a), IntMap a)
forall a. NEIntMap a -> ((Key, a), IntMap a)
deleteFindMax
{-# INLINE maxView #-}
deleteFindMax :: NEIntMap a -> ((Key, a), IntMap a)
deleteFindMax :: NEIntMap a -> ((Key, a), IntMap a)
deleteFindMax (NEIntMap Key
k a
v IntMap a
m) = ((Key, a), IntMap a)
-> (((Key, a), IntMap a) -> ((Key, a), IntMap a))
-> Maybe ((Key, a), IntMap a)
-> ((Key, a), IntMap a)
forall b a. b -> (a -> b) -> Maybe a -> b
maybe ((Key
k, a
v), IntMap a
forall a. IntMap a
M.empty) ((IntMap a -> IntMap a)
-> ((Key, a), IntMap a) -> ((Key, a), IntMap a)
forall (p :: * -> * -> *) b c a.
Bifunctor p =>
(b -> c) -> p a b -> p a c
second (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v))
(Maybe ((Key, a), IntMap a) -> ((Key, a), IntMap a))
-> (IntMap a -> Maybe ((Key, a), IntMap a))
-> IntMap a
-> ((Key, a), IntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe ((Key, a), IntMap a)
forall a. IntMap a -> Maybe ((Key, a), IntMap a)
M.maxViewWithKey
(IntMap a -> ((Key, a), IntMap a))
-> IntMap a -> ((Key, a), IntMap a)
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE deleteFindMax #-}
combineEq :: NonEmpty (Key, b) -> NonEmpty (Key, b)
combineEq :: NonEmpty (Key, b) -> NonEmpty (Key, b)
combineEq = \case
(Key, b)
x :| [] -> (Key, b)
x (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
forall a. a -> [a] -> NonEmpty a
:| []
(Key, b)
x :| xx :: [(Key, b)]
xx@((Key, b)
_:[(Key, b)]
_) -> (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
forall a b. Eq a => (a, b) -> [(a, b)] -> NonEmpty (a, b)
go (Key, b)
x [(Key, b)]
xx
where
go :: (a, b) -> [(a, b)] -> NonEmpty (a, b)
go (a, b)
z [] = (a, b)
z (a, b) -> [(a, b)] -> NonEmpty (a, b)
forall a. a -> [a] -> NonEmpty a
:| []
go z :: (a, b)
z@(a
kz,b
_) (x :: (a, b)
x@(a
kx,b
xx):[(a, b)]
xs')
| a
kxa -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
kz = (a, b) -> [(a, b)] -> NonEmpty (a, b)
go (a
kx,b
xx) [(a, b)]
xs'
| Bool
otherwise = (a, b)
z (a, b) -> NonEmpty (a, b) -> NonEmpty (a, b)
forall a. a -> NonEmpty a -> NonEmpty a
NE.<| (a, b) -> [(a, b)] -> NonEmpty (a, b)
go (a, b)
x [(a, b)]
xs'
combineEqWith
:: (Key -> b -> b -> b)
-> NonEmpty (Key, b)
-> NonEmpty (Key, b)
combineEqWith :: (Key -> b -> b -> b) -> NonEmpty (Key, b) -> NonEmpty (Key, b)
combineEqWith Key -> b -> b -> b
f = \case
(Key, b)
x :| [] -> (Key, b)
x (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
forall a. a -> [a] -> NonEmpty a
:| []
(Key, b)
x :| xx :: [(Key, b)]
xx@((Key, b)
_:[(Key, b)]
_) -> (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
go (Key, b)
x [(Key, b)]
xx
where
go :: (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
go (Key, b)
z [] = (Key, b)
z (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
forall a. a -> [a] -> NonEmpty a
:| []
go z :: (Key, b)
z@(Key
kz,b
zz) (x :: (Key, b)
x@(Key
kx,b
xx):[(Key, b)]
xs')
| Key
kxKey -> Key -> Bool
forall a. Eq a => a -> a -> Bool
==Key
kz = let yy :: b
yy = Key -> b -> b -> b
f Key
kx b
xx b
zz in (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
go (Key
kx,b
yy) [(Key, b)]
xs'
| Bool
otherwise = (Key, b)
z (Key, b) -> NonEmpty (Key, b) -> NonEmpty (Key, b)
forall a. a -> NonEmpty a -> NonEmpty a
NE.<| (Key, b) -> [(Key, b)] -> NonEmpty (Key, b)
go (Key, b)
x [(Key, b)]
xs'