{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternGuards #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE MagicHash, DeriveDataTypeable, StandaloneDeriving #-}
{-# LANGUAGE ScopedTypeVariables #-}
#endif
#if !defined(TESTING) && defined(__GLASGOW_HASKELL__)
{-# LANGUAGE Trustworthy #-}
#endif
#if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE TypeFamilies #-}
#endif
{-# OPTIONS_HADDOCK not-home #-}
{-# OPTIONS_GHC -fno-warn-incomplete-uni-patterns #-}
#include "containers.h"
module Data.IntMap.Internal (
IntMap(..), Key
, (!), (!?), (\\)
, null
, size
, member
, notMember
, lookup
, findWithDefault
, lookupLT
, lookupGT
, lookupLE
, lookupGE
, disjoint
, empty
, singleton
, insert
, insertWith
, insertWithKey
, insertLookupWithKey
, delete
, adjust
, adjustWithKey
, update
, updateWithKey
, updateLookupWithKey
, alter
, alterF
, union
, unionWith
, unionWithKey
, unions
, unionsWith
, difference
, differenceWith
, differenceWithKey
, intersection
, intersectionWith
, intersectionWithKey
, compose
, SimpleWhenMissing
, SimpleWhenMatched
, runWhenMatched
, runWhenMissing
, merge
, zipWithMaybeMatched
, zipWithMatched
, mapMaybeMissing
, dropMissing
, preserveMissing
, mapMissing
, filterMissing
, WhenMissing (..)
, WhenMatched (..)
, mergeA
, zipWithMaybeAMatched
, zipWithAMatched
, traverseMaybeMissing
, traverseMissing
, filterAMissing
, mergeWithKey
, mergeWithKey'
, map
, mapWithKey
, traverseWithKey
, traverseMaybeWithKey
, mapAccum
, mapAccumWithKey
, mapAccumRWithKey
, mapKeys
, mapKeysWith
, mapKeysMonotonic
, foldr
, foldl
, foldrWithKey
, foldlWithKey
, foldMapWithKey
, foldr'
, foldl'
, foldrWithKey'
, foldlWithKey'
, elems
, keys
, assocs
, keysSet
, fromSet
, toList
, fromList
, fromListWith
, fromListWithKey
, toAscList
, toDescList
, fromAscList
, fromAscListWith
, fromAscListWithKey
, fromDistinctAscList
, filter
, filterWithKey
, restrictKeys
, withoutKeys
, partition
, partitionWithKey
, mapMaybe
, mapMaybeWithKey
, mapEither
, mapEitherWithKey
, split
, splitLookup
, splitRoot
, isSubmapOf, isSubmapOfBy
, isProperSubmapOf, isProperSubmapOfBy
, lookupMin
, lookupMax
, findMin
, findMax
, deleteMin
, deleteMax
, deleteFindMin
, deleteFindMax
, updateMin
, updateMax
, updateMinWithKey
, updateMaxWithKey
, minView
, maxView
, minViewWithKey
, maxViewWithKey
, showTree
, showTreeWith
, Mask, Prefix, Nat
, natFromInt
, intFromNat
, link
, linkWithMask
, bin
, binCheckLeft
, binCheckRight
, zero
, nomatch
, match
, mask
, maskW
, shorter
, branchMask
, highestBitMask
, mapWhenMissing
, mapWhenMatched
, lmapWhenMissing
, contramapFirstWhenMatched
, contramapSecondWhenMatched
, mapGentlyWhenMissing
, mapGentlyWhenMatched
) where
#if MIN_VERSION_base(4,8,0)
import Data.Functor.Identity (Identity (..))
import Control.Applicative (liftA2)
#else
import Control.Applicative (Applicative(pure, (<*>)), (<$>), liftA2)
import Data.Monoid (Monoid(..))
import Data.Traversable (Traversable(traverse))
import Data.Word (Word)
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup(stimes))
#endif
#if !(MIN_VERSION_base(4,11,0)) && MIN_VERSION_base(4,9,0)
import Data.Semigroup (Semigroup((<>)))
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Semigroup (stimesIdempotentMonoid)
import Data.Functor.Classes
#endif
import Control.DeepSeq (NFData(rnf))
import Data.Bits
import qualified Data.Foldable as Foldable
#if !MIN_VERSION_base(4,8,0)
import Data.Foldable (Foldable())
#endif
import Data.Maybe (fromMaybe)
import Data.Typeable
import Prelude hiding (lookup, map, filter, foldr, foldl, null)
import Data.IntSet.Internal (Key)
import qualified Data.IntSet.Internal as IntSet
import Utils.Containers.Internal.BitUtil
import Utils.Containers.Internal.StrictPair
#if __GLASGOW_HASKELL__
import Data.Data (Data(..), Constr, mkConstr, constrIndex, Fixity(Prefix),
DataType, mkDataType)
import GHC.Exts (build)
#if !MIN_VERSION_base(4,8,0)
import Data.Functor ((<$))
#endif
#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as GHCExts
#endif
import Text.Read
#endif
import qualified Control.Category as Category
#if __GLASGOW_HASKELL__ >= 709
import Data.Coerce
#endif
type Nat = Word
natFromInt :: Key -> Nat
natFromInt :: Key -> Nat
natFromInt = Key -> Nat
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE natFromInt #-}
intFromNat :: Nat -> Key
intFromNat :: Nat -> Key
intFromNat = Nat -> Key
forall a b. (Integral a, Num b) => a -> b
fromIntegral
{-# INLINE intFromNat #-}
data IntMap a = Bin {-# UNPACK #-} !Prefix
{-# UNPACK #-} !Mask
!(IntMap a)
!(IntMap a)
| Tip {-# UNPACK #-} !Key a
| Nil
type Prefix = Int
type Mask = Int
type IntSetPrefix = Int
type IntSetBitMap = Word
bitmapOf :: Int -> IntSetBitMap
bitmapOf :: Key -> Nat
bitmapOf Key
x = Nat -> Key -> Nat
shiftLL Nat
1 (Key
x Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.suffixBitMask)
{-# INLINE bitmapOf #-}
(!) :: IntMap a -> Key -> a
(!) IntMap a
m Key
k = Key -> IntMap a -> a
forall a. Key -> IntMap a -> a
find Key
k IntMap a
m
(!?) :: IntMap a -> Key -> Maybe a
!? :: IntMap a -> Key -> Maybe a
(!?) IntMap a
m Key
k = Key -> IntMap a -> Maybe a
forall a. Key -> IntMap a -> Maybe a
lookup Key
k IntMap a
m
(\\) :: IntMap a -> IntMap b -> IntMap a
IntMap a
m1 \\ :: IntMap a -> IntMap b -> IntMap a
\\ IntMap b
m2 = IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
difference IntMap a
m1 IntMap b
m2
infixl 9 !?,\\
instance Monoid (IntMap a) where
mempty :: IntMap a
mempty = IntMap a
forall a. IntMap a
empty
mconcat :: [IntMap a] -> IntMap a
mconcat = [IntMap a] -> IntMap a
forall (f :: * -> *) a. Foldable f => f (IntMap a) -> IntMap a
unions
#if !(MIN_VERSION_base(4,9,0))
mappend = union
#else
mappend :: IntMap a -> IntMap a -> IntMap a
mappend = IntMap a -> IntMap a -> IntMap a
forall a. Semigroup a => a -> a -> a
(<>)
instance Semigroup (IntMap a) where
<> :: IntMap a -> IntMap a -> IntMap a
(<>) = IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union
stimes :: b -> IntMap a -> IntMap a
stimes = b -> IntMap a -> IntMap a
forall b a. (Integral b, Monoid a) => b -> a -> a
stimesIdempotentMonoid
#endif
instance Foldable.Foldable IntMap where
fold :: IntMap m -> m
fold = IntMap m -> m
forall m. Monoid m => IntMap m -> m
go
where go :: IntMap a -> a
go IntMap a
Nil = a
forall a. Monoid a => a
mempty
go (Tip Key
_ a
v) = a
v
go (Bin Key
_ Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = IntMap a -> a
go IntMap a
r a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` IntMap a -> a
go IntMap a
l
| Bool
otherwise = IntMap a -> a
go IntMap a
l a -> a -> a
forall a. Monoid a => a -> a -> a
`mappend` IntMap a -> a
go IntMap a
r
{-# INLINABLE fold #-}
foldr :: (a -> b -> b) -> b -> IntMap a -> b
foldr = (a -> b -> b) -> b -> IntMap a -> b
forall a b. (a -> b -> b) -> b -> IntMap a -> b
foldr
{-# INLINE foldr #-}
foldl :: (b -> a -> b) -> b -> IntMap a -> b
foldl = (b -> a -> b) -> b -> IntMap a -> b
forall b a. (b -> a -> b) -> b -> IntMap a -> b
foldl
{-# INLINE foldl #-}
foldMap :: (a -> m) -> IntMap a -> m
foldMap a -> m
f IntMap a
t = IntMap a -> m
go IntMap a
t
where go :: IntMap a -> m
go IntMap a
Nil = m
forall a. Monoid a => a
mempty
go (Tip Key
_ a
v) = a -> m
f a
v
go (Bin Key
_ Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = IntMap a -> m
go IntMap a
r m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` IntMap a -> m
go IntMap a
l
| Bool
otherwise = IntMap a -> m
go IntMap a
l m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` IntMap a -> m
go IntMap a
r
{-# INLINE foldMap #-}
foldl' :: (b -> a -> b) -> b -> IntMap a -> b
foldl' = (b -> a -> b) -> b -> IntMap a -> b
forall b a. (b -> a -> b) -> b -> IntMap a -> b
foldl'
{-# INLINE foldl' #-}
foldr' :: (a -> b -> b) -> b -> IntMap a -> b
foldr' = (a -> b -> b) -> b -> IntMap a -> b
forall a b. (a -> b -> b) -> b -> IntMap a -> b
foldr'
{-# INLINE foldr' #-}
#if MIN_VERSION_base(4,8,0)
length :: IntMap a -> Key
length = IntMap a -> Key
forall a. IntMap a -> Key
size
{-# INLINE length #-}
null :: IntMap a -> Bool
null = IntMap a -> Bool
forall a. IntMap a -> Bool
null
{-# INLINE null #-}
toList :: IntMap a -> [a]
toList = IntMap a -> [a]
forall a. IntMap a -> [a]
elems
{-# INLINE toList #-}
elem :: a -> IntMap a -> Bool
elem = a -> IntMap a -> Bool
forall a. Eq a => a -> IntMap a -> Bool
go
where go :: t -> IntMap t -> Bool
go !t
_ IntMap t
Nil = Bool
False
go t
x (Tip Key
_ t
y) = t
x t -> t -> Bool
forall a. Eq a => a -> a -> Bool
== t
y
go t
x (Bin Key
_ Key
_ IntMap t
l IntMap t
r) = t -> IntMap t -> Bool
go t
x IntMap t
l Bool -> Bool -> Bool
|| t -> IntMap t -> Bool
go t
x IntMap t
r
{-# INLINABLE elem #-}
maximum :: IntMap a -> a
maximum = IntMap a -> a
forall a. Ord a => IntMap a -> a
start
where start :: IntMap t -> t
start IntMap t
Nil = [Char] -> t
forall a. HasCallStack => [Char] -> a
error [Char]
"Data.Foldable.maximum (for Data.IntMap): empty map"
start (Tip Key
_ t
y) = t
y
start (Bin Key
_ Key
m IntMap t
l IntMap t
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = t -> IntMap t -> t
forall t. Ord t => t -> IntMap t -> t
go (IntMap t -> t
start IntMap t
r) IntMap t
l
| Bool
otherwise = t -> IntMap t -> t
forall t. Ord t => t -> IntMap t -> t
go (IntMap t -> t
start IntMap t
l) IntMap t
r
go :: t -> IntMap t -> t
go !t
m IntMap t
Nil = t
m
go t
m (Tip Key
_ t
y) = t -> t -> t
forall a. Ord a => a -> a -> a
max t
m t
y
go t
m (Bin Key
_ Key
_ IntMap t
l IntMap t
r) = t -> IntMap t -> t
go (t -> IntMap t -> t
go t
m IntMap t
l) IntMap t
r
{-# INLINABLE maximum #-}
minimum :: IntMap a -> a
minimum = IntMap a -> a
forall a. Ord a => IntMap a -> a
start
where start :: IntMap t -> t
start IntMap t
Nil = [Char] -> t
forall a. HasCallStack => [Char] -> a
error [Char]
"Data.Foldable.minimum (for Data.IntMap): empty map"
start (Tip Key
_ t
y) = t
y
start (Bin Key
_ Key
m IntMap t
l IntMap t
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = t -> IntMap t -> t
forall t. Ord t => t -> IntMap t -> t
go (IntMap t -> t
start IntMap t
r) IntMap t
l
| Bool
otherwise = t -> IntMap t -> t
forall t. Ord t => t -> IntMap t -> t
go (IntMap t -> t
start IntMap t
l) IntMap t
r
go :: t -> IntMap t -> t
go !t
m IntMap t
Nil = t
m
go t
m (Tip Key
_ t
y) = t -> t -> t
forall a. Ord a => a -> a -> a
min t
m t
y
go t
m (Bin Key
_ Key
_ IntMap t
l IntMap t
r) = t -> IntMap t -> t
go (t -> IntMap t -> t
go t
m IntMap t
l) IntMap t
r
{-# INLINABLE minimum #-}
sum :: IntMap a -> a
sum = (a -> a -> a) -> a -> IntMap a -> a
forall b a. (b -> a -> b) -> b -> IntMap a -> b
foldl' a -> a -> a
forall a. Num a => a -> a -> a
(+) a
0
{-# INLINABLE sum #-}
product :: IntMap a -> a
product = (a -> a -> a) -> a -> IntMap a -> a
forall b a. (b -> a -> b) -> b -> IntMap a -> b
foldl' a -> a -> a
forall a. Num a => a -> a -> a
(*) a
1
{-# INLINABLE product #-}
#endif
instance Traversable IntMap where
traverse :: (a -> f b) -> IntMap a -> f (IntMap b)
traverse a -> f b
f = (Key -> a -> f b) -> IntMap a -> f (IntMap b)
forall (t :: * -> *) a b.
Applicative t =>
(Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseWithKey (\Key
_ -> a -> f b
f)
{-# INLINE traverse #-}
instance NFData a => NFData (IntMap a) where
rnf :: IntMap a -> ()
rnf IntMap a
Nil = ()
rnf (Tip Key
_ a
v) = a -> ()
forall a. NFData a => a -> ()
rnf a
v
rnf (Bin Key
_ Key
_ IntMap a
l IntMap a
r) = IntMap a -> ()
forall a. NFData a => a -> ()
rnf IntMap a
l () -> () -> ()
`seq` IntMap a -> ()
forall a. NFData a => a -> ()
rnf IntMap a
r
#if __GLASGOW_HASKELL__
instance Data a => Data (IntMap a) where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> IntMap a -> c (IntMap a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z IntMap a
im = ([(Key, a)] -> IntMap a) -> c ([(Key, a)] -> IntMap a)
forall g. g -> c g
z [(Key, a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
fromList c ([(Key, a)] -> IntMap a) -> [(Key, a)] -> c (IntMap a)
forall d b. Data d => c (d -> b) -> d -> c b
`f` (IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toList IntMap a
im)
toConstr :: IntMap a -> Constr
toConstr IntMap a
_ = Constr
fromListConstr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (IntMap a)
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> Key
constrIndex Constr
c of
Key
1 -> c ([(Key, a)] -> IntMap a) -> c (IntMap a)
forall b r. Data b => c (b -> r) -> c r
k (([(Key, a)] -> IntMap a) -> c ([(Key, a)] -> IntMap a)
forall r. r -> c r
z [(Key, a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
fromList)
Key
_ -> [Char] -> c (IntMap a)
forall a. HasCallStack => [Char] -> a
error [Char]
"gunfold"
dataTypeOf :: IntMap a -> DataType
dataTypeOf IntMap a
_ = DataType
intMapDataType
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (IntMap a))
dataCast1 forall d. Data d => c (t d)
f = c (t a) -> Maybe (c (IntMap a))
forall k1 k2 (c :: k1 -> *) (t :: k2 -> k1) (t' :: k2 -> k1)
(a :: k2).
(Typeable t, Typeable t') =>
c (t a) -> Maybe (c (t' a))
gcast1 c (t a)
forall d. Data d => c (t d)
f
fromListConstr :: Constr
fromListConstr :: Constr
fromListConstr = DataType -> [Char] -> [[Char]] -> Fixity -> Constr
mkConstr DataType
intMapDataType [Char]
"fromList" [] Fixity
Prefix
intMapDataType :: DataType
intMapDataType :: DataType
intMapDataType = [Char] -> [Constr] -> DataType
mkDataType [Char]
"Data.IntMap.Internal.IntMap" [Constr
fromListConstr]
#endif
null :: IntMap a -> Bool
null :: IntMap a -> Bool
null IntMap a
Nil = Bool
True
null IntMap a
_ = Bool
False
{-# INLINE null #-}
size :: IntMap a -> Int
size :: IntMap a -> Key
size = Key -> IntMap a -> Key
forall a a. Num a => a -> IntMap a -> a
go Key
0
where
go :: a -> IntMap a -> a
go !a
acc (Bin Key
_ Key
_ IntMap a
l IntMap a
r) = a -> IntMap a -> a
go (a -> IntMap a -> a
go a
acc IntMap a
l) IntMap a
r
go a
acc (Tip Key
_ a
_) = a
1 a -> a -> a
forall a. Num a => a -> a -> a
+ a
acc
go a
acc IntMap a
Nil = a
acc
member :: Key -> IntMap a -> Bool
member :: Key -> IntMap a -> Bool
member !Key
k = IntMap a -> Bool
go
where
go :: IntMap a -> Bool
go (Bin Key
p Key
m IntMap a
l IntMap a
r) | Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = Bool
False
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> Bool
go IntMap a
l
| Bool
otherwise = IntMap a -> Bool
go IntMap a
r
go (Tip Key
kx a
_) = Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kx
go IntMap a
Nil = Bool
False
notMember :: Key -> IntMap a -> Bool
notMember :: Key -> IntMap a -> Bool
notMember Key
k IntMap a
m = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ Key -> IntMap a -> Bool
forall a. Key -> IntMap a -> Bool
member Key
k IntMap a
m
lookup :: Key -> IntMap a -> Maybe a
lookup :: Key -> IntMap a -> Maybe a
lookup !Key
k = IntMap a -> Maybe a
go
where
go :: IntMap a -> Maybe a
go (Bin Key
p Key
m IntMap a
l IntMap a
r) | Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = Maybe a
forall a. Maybe a
Nothing
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> Maybe a
go IntMap a
l
| Bool
otherwise = IntMap a -> Maybe a
go IntMap a
r
go (Tip Key
kx a
x) | Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kx = a -> Maybe a
forall a. a -> Maybe a
Just a
x
| Bool
otherwise = Maybe a
forall a. Maybe a
Nothing
go IntMap a
Nil = Maybe a
forall a. Maybe a
Nothing
find :: Key -> IntMap a -> a
find :: Key -> IntMap a -> a
find !Key
k = IntMap a -> a
go
where
go :: IntMap a -> a
go (Bin Key
p Key
m IntMap a
l IntMap a
r) | Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = a
not_found
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> a
go IntMap a
l
| Bool
otherwise = IntMap a -> a
go IntMap a
r
go (Tip Key
kx a
x) | Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kx = a
x
| Bool
otherwise = a
not_found
go IntMap a
Nil = a
not_found
not_found :: a
not_found = [Char] -> a
forall a. HasCallStack => [Char] -> a
error ([Char]
"IntMap.!: key " [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ Key -> [Char]
forall a. Show a => a -> [Char]
show Key
k [Char] -> [Char] -> [Char]
forall a. [a] -> [a] -> [a]
++ [Char]
" is not an element of the map")
findWithDefault :: a -> Key -> IntMap a -> a
findWithDefault :: a -> Key -> IntMap a -> a
findWithDefault a
def !Key
k = IntMap a -> a
go
where
go :: IntMap a -> a
go (Bin Key
p Key
m IntMap a
l IntMap a
r) | Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = a
def
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> a
go IntMap a
l
| Bool
otherwise = IntMap a -> a
go IntMap a
r
go (Tip Key
kx a
x) | Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kx = a
x
| Bool
otherwise = a
def
go IntMap a
Nil = a
def
lookupLT :: Key -> IntMap a -> Maybe (Key, a)
lookupLT :: Key -> IntMap a -> Maybe (Key, a)
lookupLT !Key
k IntMap a
t = case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
>= Key
0 then IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
r IntMap a
l else IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
r
IntMap a
_ -> IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
t
where
go :: IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
p then IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
def else IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
r
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def IntMap a
l
| Bool
otherwise = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
l IntMap a
r
go IntMap a
def (Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
<= Key
ky = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
def
| Bool
otherwise = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
ky, a
y)
go IntMap a
def IntMap a
Nil = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
def
lookupGT :: Key -> IntMap a -> Maybe (Key, a)
lookupGT :: Key -> IntMap a -> Maybe (Key, a)
lookupGT !Key
k IntMap a
t = case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
>= Key
0 then IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
l else IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
l IntMap a
r
IntMap a
_ -> IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
t
where
go :: IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
p then IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
l else IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
def
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
r IntMap a
l
| Bool
otherwise = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def IntMap a
r
go IntMap a
def (Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
>= Key
ky = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
def
| Bool
otherwise = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
ky, a
y)
go IntMap a
def IntMap a
Nil = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
def
lookupLE :: Key -> IntMap a -> Maybe (Key, a)
lookupLE :: Key -> IntMap a -> Maybe (Key, a)
lookupLE !Key
k IntMap a
t = case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
>= Key
0 then IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
r IntMap a
l else IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
r
IntMap a
_ -> IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
t
where
go :: IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
p then IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
def else IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
r
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def IntMap a
l
| Bool
otherwise = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
l IntMap a
r
go IntMap a
def (Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
ky = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
def
| Bool
otherwise = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
ky, a
y)
go IntMap a
def IntMap a
Nil = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
def
lookupGE :: Key -> IntMap a -> Maybe (Key, a)
lookupGE :: Key -> IntMap a -> Maybe (Key, a)
lookupGE !Key
k IntMap a
t = case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
>= Key
0 then IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
l else IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
l IntMap a
r
IntMap a
_ -> IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
forall a. IntMap a
Nil IntMap a
t
where
go :: IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
p then IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
l else IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
def
| Key -> Key -> Bool
zero Key
k Key
m = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
r IntMap a
l
| Bool
otherwise = IntMap a -> IntMap a -> Maybe (Key, a)
go IntMap a
def IntMap a
r
go IntMap a
def (Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
ky = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
def
| Bool
otherwise = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
ky, a
y)
go IntMap a
def IntMap a
Nil = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
def
unsafeFindMin :: IntMap a -> Maybe (Key, a)
unsafeFindMin :: IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
Nil = Maybe (Key, a)
forall a. Maybe a
Nothing
unsafeFindMin (Tip Key
ky a
y) = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
ky, a
y)
unsafeFindMin (Bin Key
_ Key
_ IntMap a
l IntMap a
_) = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMin IntMap a
l
unsafeFindMax :: IntMap a -> Maybe (Key, a)
unsafeFindMax :: IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
Nil = Maybe (Key, a)
forall a. Maybe a
Nothing
unsafeFindMax (Tip Key
ky a
y) = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
ky, a
y)
unsafeFindMax (Bin Key
_ Key
_ IntMap a
_ IntMap a
r) = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
unsafeFindMax IntMap a
r
disjoint :: IntMap a -> IntMap b -> Bool
disjoint :: IntMap a -> IntMap b -> Bool
disjoint IntMap a
Nil IntMap b
_ = Bool
True
disjoint IntMap a
_ IntMap b
Nil = Bool
True
disjoint (Tip Key
kx a
_) IntMap b
ys = Key -> IntMap b -> Bool
forall a. Key -> IntMap a -> Bool
notMember Key
kx IntMap b
ys
disjoint IntMap a
xs (Tip Key
ky b
_) = Key -> IntMap a -> Bool
forall a. Key -> IntMap a -> Bool
notMember Key
ky IntMap a
xs
disjoint t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) t2 :: IntMap b
t2@(Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
| Key -> Key -> Bool
shorter Key
m1 Key
m2 = Bool
disjoint1
| Key -> Key -> Bool
shorter Key
m2 Key
m1 = Bool
disjoint2
| Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2 = IntMap a -> IntMap b -> Bool
forall a b. IntMap a -> IntMap b -> Bool
disjoint IntMap a
l1 IntMap b
l2 Bool -> Bool -> Bool
&& IntMap a -> IntMap b -> Bool
forall a b. IntMap a -> IntMap b -> Bool
disjoint IntMap a
r1 IntMap b
r2
| Bool
otherwise = Bool
True
where
disjoint1 :: Bool
disjoint1 | Key -> Key -> Key -> Bool
nomatch Key
p2 Key
p1 Key
m1 = Bool
True
| Key -> Key -> Bool
zero Key
p2 Key
m1 = IntMap a -> IntMap b -> Bool
forall a b. IntMap a -> IntMap b -> Bool
disjoint IntMap a
l1 IntMap b
t2
| Bool
otherwise = IntMap a -> IntMap b -> Bool
forall a b. IntMap a -> IntMap b -> Bool
disjoint IntMap a
r1 IntMap b
t2
disjoint2 :: Bool
disjoint2 | Key -> Key -> Key -> Bool
nomatch Key
p1 Key
p2 Key
m2 = Bool
True
| Key -> Key -> Bool
zero Key
p1 Key
m2 = IntMap a -> IntMap b -> Bool
forall a b. IntMap a -> IntMap b -> Bool
disjoint IntMap a
t1 IntMap b
l2
| Bool
otherwise = IntMap a -> IntMap b -> Bool
forall a b. IntMap a -> IntMap b -> Bool
disjoint IntMap a
t1 IntMap b
r2
compose :: IntMap c -> IntMap Int -> IntMap c
compose :: IntMap c -> IntMap Key -> IntMap c
compose IntMap c
bc !IntMap Key
ab
| IntMap c -> Bool
forall a. IntMap a -> Bool
null IntMap c
bc = IntMap c
forall a. IntMap a
empty
| Bool
otherwise = (Key -> Maybe c) -> IntMap Key -> IntMap c
forall a b. (a -> Maybe b) -> IntMap a -> IntMap b
mapMaybe (IntMap c
bc IntMap c -> Key -> Maybe c
forall a. IntMap a -> Key -> Maybe a
!?) IntMap Key
ab
empty :: IntMap a
empty :: IntMap a
empty
= IntMap a
forall a. IntMap a
Nil
{-# INLINE empty #-}
singleton :: Key -> a -> IntMap a
singleton :: Key -> a -> IntMap a
singleton Key
k a
x
= Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x
{-# INLINE singleton #-}
insert :: Key -> a -> IntMap a -> IntMap a
insert :: Key -> a -> IntMap a -> IntMap a
insert !Key
k a
x t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
p IntMap a
t
| Key -> Key -> Bool
zero Key
k Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insert Key
k a
x IntMap a
l) IntMap a
r
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l (Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insert Key
k a
x IntMap a
r)
insert Key
k a
x t :: IntMap a
t@(Tip Key
ky a
_)
| Key
kKey -> Key -> Bool
forall a. Eq a => a -> a -> Bool
==Key
ky = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x
| Bool
otherwise = Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
ky IntMap a
t
insert Key
k a
x IntMap a
Nil = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x
insertWith :: (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWith :: (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWith a -> a -> a
f Key
k a
x IntMap a
t
= (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWithKey (\Key
_ a
x' a
y' -> a -> a -> a
f a
x' a
y') Key
k a
x IntMap a
t
insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWithKey Key -> a -> a -> a
f !Key
k a
x t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
p IntMap a
t
| Key -> Key -> Bool
zero Key
k Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m ((Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWithKey Key -> a -> a -> a
f Key
k a
x IntMap a
l) IntMap a
r
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l ((Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWithKey Key -> a -> a -> a
f Key
k a
x IntMap a
r)
insertWithKey Key -> a -> a -> a
f Key
k a
x t :: IntMap a
t@(Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k (Key -> a -> a -> a
f Key
k a
x a
y)
| Bool
otherwise = Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
ky IntMap a
t
insertWithKey Key -> a -> a -> a
_ Key
k a
x IntMap a
Nil = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x
insertLookupWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a)
insertLookupWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a)
insertLookupWithKey Key -> a -> a -> a
f !Key
k a
x t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = (Maybe a
forall a. Maybe a
Nothing,Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
p IntMap a
t)
| Key -> Key -> Bool
zero Key
k Key
m = let (Maybe a
found,IntMap a
l') = (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)
insertLookupWithKey Key -> a -> a -> a
f Key
k a
x IntMap a
l
in (Maybe a
found,Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l' IntMap a
r)
| Bool
otherwise = let (Maybe a
found,IntMap a
r') = (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)
insertLookupWithKey Key -> a -> a -> a
f Key
k a
x IntMap a
r
in (Maybe a
found,Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l IntMap a
r')
insertLookupWithKey Key -> a -> a -> a
f Key
k a
x t :: IntMap a
t@(Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky = (a -> Maybe a
forall a. a -> Maybe a
Just a
y,Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k (Key -> a -> a -> a
f Key
k a
x a
y))
| Bool
otherwise = (Maybe a
forall a. Maybe a
Nothing,Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
ky IntMap a
t)
insertLookupWithKey Key -> a -> a -> a
_ Key
k a
x IntMap a
Nil = (Maybe a
forall a. Maybe a
Nothing,Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x)
delete :: Key -> IntMap a -> IntMap a
delete :: Key -> IntMap a -> IntMap a
delete !Key
k t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = IntMap a
t
| Key -> Key -> Bool
zero Key
k Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m (Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> IntMap a
delete Key
k IntMap a
l) IntMap a
r
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l (Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> IntMap a
delete Key
k IntMap a
r)
delete Key
k t :: IntMap a
t@(Tip Key
ky a
_)
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky = IntMap a
forall a. IntMap a
Nil
| Bool
otherwise = IntMap a
t
delete Key
_k IntMap a
Nil = IntMap a
forall a. IntMap a
Nil
adjust :: (a -> a) -> Key -> IntMap a -> IntMap a
adjust :: (a -> a) -> Key -> IntMap a -> IntMap a
adjust a -> a
f Key
k IntMap a
m
= (Key -> a -> a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> a) -> Key -> IntMap a -> IntMap a
adjustWithKey (\Key
_ a
x -> a -> a
f a
x) Key
k IntMap a
m
adjustWithKey :: (Key -> a -> a) -> Key -> IntMap a -> IntMap a
adjustWithKey :: (Key -> a -> a) -> Key -> IntMap a -> IntMap a
adjustWithKey Key -> a -> a
f !Key
k t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = IntMap a
t
| Key -> Key -> Bool
zero Key
k Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m ((Key -> a -> a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> a) -> Key -> IntMap a -> IntMap a
adjustWithKey Key -> a -> a
f Key
k IntMap a
l) IntMap a
r
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l ((Key -> a -> a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> a) -> Key -> IntMap a -> IntMap a
adjustWithKey Key -> a -> a
f Key
k IntMap a
r)
adjustWithKey Key -> a -> a
f Key
k t :: IntMap a
t@(Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
ky (Key -> a -> a
f Key
k a
y)
| Bool
otherwise = IntMap a
t
adjustWithKey Key -> a -> a
_ Key
_ IntMap a
Nil = IntMap a
forall a. IntMap a
Nil
update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a
update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a
update a -> Maybe a
f
= (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
updateWithKey (\Key
_ a
x -> a -> Maybe a
f a
x)
updateWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
updateWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
updateWithKey Key -> a -> Maybe a
f !Key
k t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = IntMap a
t
| Key -> Key -> Bool
zero Key
k Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m ((Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
updateWithKey Key -> a -> Maybe a
f Key
k IntMap a
l) IntMap a
r
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l ((Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
updateWithKey Key -> a -> Maybe a
f Key
k IntMap a
r)
updateWithKey Key -> a -> Maybe a
f Key
k t :: IntMap a
t@(Tip Key
ky a
y)
| Key
k Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky = case (Key -> a -> Maybe a
f Key
k a
y) of
Just a
y' -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
ky a
y'
Maybe a
Nothing -> IntMap a
forall a. IntMap a
Nil
| Bool
otherwise = IntMap a
t
updateWithKey Key -> a -> Maybe a
_ Key
_ IntMap a
Nil = IntMap a
forall a. IntMap a
Nil
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a,IntMap a)
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
updateLookupWithKey Key -> a -> Maybe a
f !Key
k t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = (Maybe a
forall a. Maybe a
Nothing,IntMap a
t)
| Key -> Key -> Bool
zero Key
k Key
m = let !(Maybe a
found,IntMap a
l') = (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
forall a.
(Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
updateLookupWithKey Key -> a -> Maybe a
f Key
k IntMap a
l
in (Maybe a
found,Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m IntMap a
l' IntMap a
r)
| Bool
otherwise = let !(Maybe a
found,IntMap a
r') = (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
forall a.
(Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
updateLookupWithKey Key -> a -> Maybe a
f Key
k IntMap a
r
in (Maybe a
found,Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l IntMap a
r')
updateLookupWithKey Key -> a -> Maybe a
f Key
k t :: IntMap a
t@(Tip Key
ky a
y)
| Key
kKey -> Key -> Bool
forall a. Eq a => a -> a -> Bool
==Key
ky = case (Key -> a -> Maybe a
f Key
k a
y) of
Just a
y' -> (a -> Maybe a
forall a. a -> Maybe a
Just a
y,Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
ky a
y')
Maybe a
Nothing -> (a -> Maybe a
forall a. a -> Maybe a
Just a
y,IntMap a
forall a. IntMap a
Nil)
| Bool
otherwise = (Maybe a
forall a. Maybe a
Nothing,IntMap a
t)
updateLookupWithKey Key -> a -> Maybe a
_ Key
_ IntMap a
Nil = (Maybe a
forall a. Maybe a
Nothing,IntMap a
forall a. IntMap a
Nil)
alter :: (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
alter :: (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
alter Maybe a -> Maybe a
f !Key
k t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k Key
p Key
m = case Maybe a -> Maybe a
f Maybe a
forall a. Maybe a
Nothing of
Maybe a
Nothing -> IntMap a
t
Just a
x -> Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
p IntMap a
t
| Key -> Key -> Bool
zero Key
k Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m ((Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
alter Maybe a -> Maybe a
f Key
k IntMap a
l) IntMap a
r
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l ((Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
forall a. (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
alter Maybe a -> Maybe a
f Key
k IntMap a
r)
alter Maybe a -> Maybe a
f Key
k t :: IntMap a
t@(Tip Key
ky a
y)
| Key
kKey -> Key -> Bool
forall a. Eq a => a -> a -> Bool
==Key
ky = case Maybe a -> Maybe a
f (a -> Maybe a
forall a. a -> Maybe a
Just a
y) of
Just a
x -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
ky a
x
Maybe a
Nothing -> IntMap a
forall a. IntMap a
Nil
| Bool
otherwise = case Maybe a -> Maybe a
f Maybe a
forall a. Maybe a
Nothing of
Just a
x -> Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x) Key
ky IntMap a
t
Maybe a
Nothing -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
ky a
y
alter Maybe a -> Maybe a
f Key
k IntMap a
Nil = case Maybe a -> Maybe a
f Maybe a
forall a. Maybe a
Nothing of
Just a
x -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
x
Maybe a
Nothing -> IntMap a
forall a. IntMap a
Nil
alterF :: Functor f
=> (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a)
alterF :: (Maybe a -> f (Maybe a)) -> Key -> IntMap a -> f (IntMap a)
alterF Maybe a -> f (Maybe a)
f Key
k IntMap a
m = ((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
mv) ((Maybe a -> IntMap a) -> f (IntMap a))
-> (Maybe a -> IntMap a) -> f (IntMap a)
forall a b. (a -> b) -> a -> b
$ \Maybe a
fres ->
case Maybe a
fres of
Maybe a
Nothing -> IntMap a -> (a -> IntMap a) -> Maybe a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a
m (IntMap a -> a -> IntMap a
forall a b. a -> b -> a
const (Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> IntMap a
delete Key
k IntMap a
m)) Maybe a
mv
Just a
v' -> Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insert Key
k a
v' IntMap a
m
where mv :: Maybe a
mv = Key -> IntMap a -> Maybe a
forall a. Key -> IntMap a -> Maybe a
lookup Key
k IntMap a
m
unions :: Foldable f => f (IntMap a) -> IntMap a
unions :: f (IntMap a) -> IntMap a
unions f (IntMap a)
xs
= (IntMap a -> IntMap a -> IntMap a)
-> IntMap a -> f (IntMap a) -> IntMap a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl' IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union IntMap a
forall a. IntMap a
empty f (IntMap a)
xs
unionsWith :: Foldable f => (a->a->a) -> f (IntMap a) -> IntMap a
unionsWith :: (a -> a -> a) -> f (IntMap a) -> IntMap a
unionsWith a -> a -> a
f f (IntMap a)
ts
= (IntMap a -> IntMap a -> IntMap a)
-> IntMap a -> f (IntMap a) -> IntMap a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl' ((a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
unionWith a -> a -> a
f) IntMap a
forall a. IntMap a
empty f (IntMap a)
ts
union :: IntMap a -> IntMap a -> IntMap a
union :: IntMap a -> IntMap a -> IntMap a
union IntMap a
m1 IntMap a
m2
= (Key -> Key -> IntMap a -> IntMap a -> IntMap a)
-> (IntMap a -> IntMap a -> IntMap a)
-> (IntMap a -> IntMap a)
-> (IntMap a -> IntMap a)
-> IntMap a
-> IntMap a
-> IntMap a
forall c a b.
(Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey' Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin IntMap a -> IntMap a -> IntMap a
forall a b. a -> b -> a
const IntMap a -> IntMap a
forall a. a -> a
id IntMap a -> IntMap a
forall a. a -> a
id IntMap a
m1 IntMap a
m2
unionWith :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
unionWith :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
unionWith a -> a -> a
f IntMap a
m1 IntMap a
m2
= (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
unionWithKey (\Key
_ a
x a
y -> a -> a -> a
f a
x a
y) IntMap a
m1 IntMap a
m2
unionWithKey :: (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
unionWithKey :: (Key -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
unionWithKey Key -> a -> a -> a
f IntMap a
m1 IntMap a
m2
= (Key -> Key -> IntMap a -> IntMap a -> IntMap a)
-> (IntMap a -> IntMap a -> IntMap a)
-> (IntMap a -> IntMap a)
-> (IntMap a -> IntMap a)
-> IntMap a
-> IntMap a
-> IntMap a
forall c a b.
(Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey' Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin (\(Tip Key
k1 a
x1) (Tip Key
_k2 a
x2) -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k1 (Key -> a -> a -> a
f Key
k1 a
x1 a
x2)) IntMap a -> IntMap a
forall a. a -> a
id IntMap a -> IntMap a
forall a. a -> a
id IntMap a
m1 IntMap a
m2
difference :: IntMap a -> IntMap b -> IntMap a
difference :: IntMap a -> IntMap b -> IntMap a
difference IntMap a
m1 IntMap b
m2
= (Key -> a -> b -> Maybe a)
-> (IntMap a -> IntMap a)
-> (IntMap b -> IntMap a)
-> IntMap a
-> IntMap b
-> IntMap a
forall a b c.
(Key -> a -> b -> Maybe c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey (\Key
_ a
_ b
_ -> Maybe a
forall a. Maybe a
Nothing) IntMap a -> IntMap a
forall a. a -> a
id (IntMap a -> IntMap b -> IntMap a
forall a b. a -> b -> a
const IntMap a
forall a. IntMap a
Nil) IntMap a
m1 IntMap b
m2
differenceWith :: (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
differenceWith :: (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
differenceWith a -> b -> Maybe a
f IntMap a
m1 IntMap b
m2
= (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
differenceWithKey (\Key
_ a
x b
y -> a -> b -> Maybe a
f a
x b
y) IntMap a
m1 IntMap b
m2
differenceWithKey :: (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
differenceWithKey :: (Key -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
differenceWithKey Key -> a -> b -> Maybe a
f IntMap a
m1 IntMap b
m2
= (Key -> a -> b -> Maybe a)
-> (IntMap a -> IntMap a)
-> (IntMap b -> IntMap a)
-> IntMap a
-> IntMap b
-> IntMap a
forall a b c.
(Key -> a -> b -> Maybe c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey Key -> a -> b -> Maybe a
f IntMap a -> IntMap a
forall a. a -> a
id (IntMap a -> IntMap b -> IntMap a
forall a b. a -> b -> a
const IntMap a
forall a. IntMap a
Nil) IntMap a
m1 IntMap b
m2
withoutKeys :: IntMap a -> IntSet.IntSet -> IntMap a
withoutKeys :: IntMap a -> IntSet -> IntMap a
withoutKeys t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) t2 :: IntSet
t2@(IntSet.Bin Key
p2 Key
m2 IntSet
l2 IntSet
r2)
| Key -> Key -> Bool
shorter Key
m1 Key
m2 = IntMap a
difference1
| Key -> Key -> Bool
shorter Key
m2 Key
m1 = IntMap a
difference2
| Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2 = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p1 Key
m1 (IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
withoutKeys IntMap a
l1 IntSet
l2) (IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
withoutKeys IntMap a
r1 IntSet
r2)
| Bool
otherwise = IntMap a
t1
where
difference1 :: IntMap a
difference1
| Key -> Key -> Key -> Bool
nomatch Key
p2 Key
p1 Key
m1 = IntMap a
t1
| Key -> Key -> Bool
zero Key
p2 Key
m1 = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p1 Key
m1 (IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
withoutKeys IntMap a
l1 IntSet
t2) IntMap a
r1
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p1 Key
m1 IntMap a
l1 (IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
withoutKeys IntMap a
r1 IntSet
t2)
difference2 :: IntMap a
difference2
| Key -> Key -> Key -> Bool
nomatch Key
p1 Key
p2 Key
m2 = IntMap a
t1
| Key -> Key -> Bool
zero Key
p1 Key
m2 = IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
withoutKeys IntMap a
t1 IntSet
l2
| Bool
otherwise = IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
withoutKeys IntMap a
t1 IntSet
r2
withoutKeys t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
_ IntMap a
_) (IntSet.Tip Key
p2 Nat
bm2) =
let minbit :: Nat
minbit = Key -> Nat
bitmapOf Key
p1
lt_minbit :: Nat
lt_minbit = Nat
minbit Nat -> Nat -> Nat
forall a. Num a => a -> a -> a
- Nat
1
maxbit :: Nat
maxbit = Key -> Nat
bitmapOf (Key
p1 Key -> Key -> Key
forall a. Bits a => a -> a -> a
.|. (Key
m1 Key -> Key -> Key
forall a. Bits a => a -> a -> a
.|. (Key
m1 Key -> Key -> Key
forall a. Num a => a -> a -> a
- Key
1)))
gt_maxbit :: Nat
gt_maxbit = (-Nat
maxbit) Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
`xor` Nat
maxbit
in Key -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
forall a. Key -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
updatePrefix Key
p2 IntMap a
t1 ((IntMap a -> IntMap a) -> IntMap a)
-> (IntMap a -> IntMap a) -> IntMap a
forall a b. (a -> b) -> a -> b
$ Nat -> IntMap a -> IntMap a
forall a. Nat -> IntMap a -> IntMap a
withoutBM (Nat
bm2 Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.|. Nat
lt_minbit Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.|. Nat
gt_maxbit)
withoutKeys t1 :: IntMap a
t1@(Bin Key
_ Key
_ IntMap a
_ IntMap a
_) IntSet
IntSet.Nil = IntMap a
t1
withoutKeys t1 :: IntMap a
t1@(Tip Key
k1 a
_) IntSet
t2
| Key
k1 Key -> IntSet -> Bool
`IntSet.member` IntSet
t2 = IntMap a
forall a. IntMap a
Nil
| Bool
otherwise = IntMap a
t1
withoutKeys IntMap a
Nil IntSet
_ = IntMap a
forall a. IntMap a
Nil
updatePrefix
:: IntSetPrefix -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
updatePrefix :: Key -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
updatePrefix !Key
kp t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r) IntMap a -> IntMap a
f
| Key
m Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.suffixBitMask Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0 =
if Key
p Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.prefixBitMask Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kp then IntMap a -> IntMap a
f IntMap a
t else IntMap a
t
| Key -> Key -> Key -> Bool
nomatch Key
kp Key
p Key
m = IntMap a
t
| Key -> Key -> Bool
zero Key
kp Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m (Key -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
forall a. Key -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
updatePrefix Key
kp IntMap a
l IntMap a -> IntMap a
f) IntMap a
r
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l (Key -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
forall a. Key -> IntMap a -> (IntMap a -> IntMap a) -> IntMap a
updatePrefix Key
kp IntMap a
r IntMap a -> IntMap a
f)
updatePrefix Key
kp t :: IntMap a
t@(Tip Key
kx a
_) IntMap a -> IntMap a
f
| Key
kx Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.prefixBitMask Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kp = IntMap a -> IntMap a
f IntMap a
t
| Bool
otherwise = IntMap a
t
updatePrefix Key
_ IntMap a
Nil IntMap a -> IntMap a
_ = IntMap a
forall a. IntMap a
Nil
withoutBM :: IntSetBitMap -> IntMap a -> IntMap a
withoutBM :: Nat -> IntMap a -> IntMap a
withoutBM Nat
0 IntMap a
t = IntMap a
t
withoutBM Nat
bm (Bin Key
p Key
m IntMap a
l IntMap a
r) =
let leftBits :: Nat
leftBits = Key -> Nat
bitmapOf (Key
p Key -> Key -> Key
forall a. Bits a => a -> a -> a
.|. Key
m) Nat -> Nat -> Nat
forall a. Num a => a -> a -> a
- Nat
1
bmL :: Nat
bmL = Nat
bm Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. Nat
leftBits
bmR :: Nat
bmR = Nat
bm Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
`xor` Nat
bmL
in Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m (Nat -> IntMap a -> IntMap a
forall a. Nat -> IntMap a -> IntMap a
withoutBM Nat
bmL IntMap a
l) (Nat -> IntMap a -> IntMap a
forall a. Nat -> IntMap a -> IntMap a
withoutBM Nat
bmR IntMap a
r)
withoutBM Nat
bm t :: IntMap a
t@(Tip Key
k a
_)
| Key
k Key -> IntSet -> Bool
`IntSet.member` Key -> Nat -> IntSet
IntSet.Tip (Key
k Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.prefixBitMask) Nat
bm = IntMap a
forall a. IntMap a
Nil
| Bool
otherwise = IntMap a
t
withoutBM Nat
_ IntMap a
Nil = IntMap a
forall a. IntMap a
Nil
intersection :: IntMap a -> IntMap b -> IntMap a
intersection :: IntMap a -> IntMap b -> IntMap a
intersection IntMap a
m1 IntMap b
m2
= (Key -> Key -> IntMap a -> IntMap a -> IntMap a)
-> (IntMap a -> IntMap b -> IntMap a)
-> (IntMap a -> IntMap a)
-> (IntMap b -> IntMap a)
-> IntMap a
-> IntMap b
-> IntMap a
forall c a b.
(Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey' Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin IntMap a -> IntMap b -> IntMap a
forall a b. a -> b -> a
const (IntMap a -> IntMap a -> IntMap a
forall a b. a -> b -> a
const IntMap a
forall a. IntMap a
Nil) (IntMap a -> IntMap b -> IntMap a
forall a b. a -> b -> a
const IntMap a
forall a. IntMap a
Nil) IntMap a
m1 IntMap b
m2
restrictKeys :: IntMap a -> IntSet.IntSet -> IntMap a
restrictKeys :: IntMap a -> IntSet -> IntMap a
restrictKeys t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) t2 :: IntSet
t2@(IntSet.Bin Key
p2 Key
m2 IntSet
l2 IntSet
r2)
| Key -> Key -> Bool
shorter Key
m1 Key
m2 = IntMap a
intersection1
| Key -> Key -> Bool
shorter Key
m2 Key
m1 = IntMap a
intersection2
| Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2 = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p1 Key
m1 (IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
restrictKeys IntMap a
l1 IntSet
l2) (IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
restrictKeys IntMap a
r1 IntSet
r2)
| Bool
otherwise = IntMap a
forall a. IntMap a
Nil
where
intersection1 :: IntMap a
intersection1
| Key -> Key -> Key -> Bool
nomatch Key
p2 Key
p1 Key
m1 = IntMap a
forall a. IntMap a
Nil
| Key -> Key -> Bool
zero Key
p2 Key
m1 = IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
restrictKeys IntMap a
l1 IntSet
t2
| Bool
otherwise = IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
restrictKeys IntMap a
r1 IntSet
t2
intersection2 :: IntMap a
intersection2
| Key -> Key -> Key -> Bool
nomatch Key
p1 Key
p2 Key
m2 = IntMap a
forall a. IntMap a
Nil
| Key -> Key -> Bool
zero Key
p1 Key
m2 = IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
restrictKeys IntMap a
t1 IntSet
l2
| Bool
otherwise = IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
restrictKeys IntMap a
t1 IntSet
r2
restrictKeys t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
_ IntMap a
_) (IntSet.Tip Key
p2 Nat
bm2) =
let minbit :: Nat
minbit = Key -> Nat
bitmapOf Key
p1
ge_minbit :: Nat
ge_minbit = Nat -> Nat
forall a. Bits a => a -> a
complement (Nat
minbit Nat -> Nat -> Nat
forall a. Num a => a -> a -> a
- Nat
1)
maxbit :: Nat
maxbit = Key -> Nat
bitmapOf (Key
p1 Key -> Key -> Key
forall a. Bits a => a -> a -> a
.|. (Key
m1 Key -> Key -> Key
forall a. Bits a => a -> a -> a
.|. (Key
m1 Key -> Key -> Key
forall a. Num a => a -> a -> a
- Key
1)))
le_maxbit :: Nat
le_maxbit = Nat
maxbit Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.|. (Nat
maxbit Nat -> Nat -> Nat
forall a. Num a => a -> a -> a
- Nat
1)
in Nat -> IntMap a -> IntMap a
forall a. Nat -> IntMap a -> IntMap a
restrictBM (Nat
bm2 Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. Nat
ge_minbit Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. Nat
le_maxbit) (Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> IntMap a
lookupPrefix Key
p2 IntMap a
t1)
restrictKeys (Bin Key
_ Key
_ IntMap a
_ IntMap a
_) IntSet
IntSet.Nil = IntMap a
forall a. IntMap a
Nil
restrictKeys t1 :: IntMap a
t1@(Tip Key
k1 a
_) IntSet
t2
| Key
k1 Key -> IntSet -> Bool
`IntSet.member` IntSet
t2 = IntMap a
t1
| Bool
otherwise = IntMap a
forall a. IntMap a
Nil
restrictKeys IntMap a
Nil IntSet
_ = IntMap a
forall a. IntMap a
Nil
lookupPrefix :: IntSetPrefix -> IntMap a -> IntMap a
lookupPrefix :: Key -> IntMap a -> IntMap a
lookupPrefix !Key
kp t :: IntMap a
t@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.suffixBitMask Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
0 =
if Key
p Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.prefixBitMask Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kp then IntMap a
t else IntMap a
forall a. IntMap a
Nil
| Key -> Key -> Key -> Bool
nomatch Key
kp Key
p Key
m = IntMap a
forall a. IntMap a
Nil
| Key -> Key -> Bool
zero Key
kp Key
m = Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> IntMap a
lookupPrefix Key
kp IntMap a
l
| Bool
otherwise = Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> IntMap a
lookupPrefix Key
kp IntMap a
r
lookupPrefix Key
kp t :: IntMap a
t@(Tip Key
kx a
_)
| (Key
kx Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.prefixBitMask) Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
kp = IntMap a
t
| Bool
otherwise = IntMap a
forall a. IntMap a
Nil
lookupPrefix Key
_ IntMap a
Nil = IntMap a
forall a. IntMap a
Nil
restrictBM :: IntSetBitMap -> IntMap a -> IntMap a
restrictBM :: Nat -> IntMap a -> IntMap a
restrictBM Nat
0 IntMap a
_ = IntMap a
forall a. IntMap a
Nil
restrictBM Nat
bm (Bin Key
p Key
m IntMap a
l IntMap a
r) =
let leftBits :: Nat
leftBits = Key -> Nat
bitmapOf (Key
p Key -> Key -> Key
forall a. Bits a => a -> a -> a
.|. Key
m) Nat -> Nat -> Nat
forall a. Num a => a -> a -> a
- Nat
1
bmL :: Nat
bmL = Nat
bm Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. Nat
leftBits
bmR :: Nat
bmR = Nat
bm Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
`xor` Nat
bmL
in Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m (Nat -> IntMap a -> IntMap a
forall a. Nat -> IntMap a -> IntMap a
restrictBM Nat
bmL IntMap a
l) (Nat -> IntMap a -> IntMap a
forall a. Nat -> IntMap a -> IntMap a
restrictBM Nat
bmR IntMap a
r)
restrictBM Nat
bm t :: IntMap a
t@(Tip Key
k a
_)
| Key
k Key -> IntSet -> Bool
`IntSet.member` Key -> Nat -> IntSet
IntSet.Tip (Key
k Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.prefixBitMask) Nat
bm = IntMap a
t
| Bool
otherwise = IntMap a
forall a. IntMap a
Nil
restrictBM Nat
_ IntMap a
Nil = IntMap a
forall a. IntMap a
Nil
intersectionWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
intersectionWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
intersectionWith a -> b -> c
f IntMap a
m1 IntMap b
m2
= (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c.
(Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
intersectionWithKey (\Key
_ a
x b
y -> a -> b -> c
f a
x b
y) IntMap a
m1 IntMap b
m2
intersectionWithKey :: (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
intersectionWithKey :: (Key -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
intersectionWithKey Key -> a -> b -> c
f IntMap a
m1 IntMap b
m2
= (Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
forall c a b.
(Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey' Key -> Key -> IntMap c -> IntMap c -> IntMap c
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin (\(Tip Key
k1 a
x1) (Tip Key
_k2 b
x2) -> Key -> c -> IntMap c
forall a. Key -> a -> IntMap a
Tip Key
k1 (Key -> a -> b -> c
f Key
k1 a
x1 b
x2)) (IntMap c -> IntMap a -> IntMap c
forall a b. a -> b -> a
const IntMap c
forall a. IntMap a
Nil) (IntMap c -> IntMap b -> IntMap c
forall a b. a -> b -> a
const IntMap c
forall a. IntMap a
Nil) IntMap a
m1 IntMap b
m2
mergeWithKey :: (Key -> a -> b -> Maybe c) -> (IntMap a -> IntMap c) -> (IntMap b -> IntMap c)
-> IntMap a -> IntMap b -> IntMap c
mergeWithKey :: (Key -> a -> b -> Maybe c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey Key -> a -> b -> Maybe c
f IntMap a -> IntMap c
g1 IntMap b -> IntMap c
g2 = (Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
forall c a b.
(Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey' Key -> Key -> IntMap c -> IntMap c -> IntMap c
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin IntMap a -> IntMap b -> IntMap c
combine IntMap a -> IntMap c
g1 IntMap b -> IntMap c
g2
where
combine :: IntMap a -> IntMap b -> IntMap c
combine = \(Tip Key
k1 a
x1) (Tip Key
_k2 b
x2) ->
case Key -> a -> b -> Maybe c
f Key
k1 a
x1 b
x2 of
Maybe c
Nothing -> IntMap c
forall a. IntMap a
Nil
Just c
x -> Key -> c -> IntMap c
forall a. Key -> a -> IntMap a
Tip Key
k1 c
x
{-# INLINE combine #-}
{-# INLINE mergeWithKey #-}
mergeWithKey' :: (Prefix -> Mask -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c) -> (IntMap a -> IntMap c) -> (IntMap b -> IntMap c)
-> IntMap a -> IntMap b -> IntMap c
mergeWithKey' :: (Key -> Key -> IntMap c -> IntMap c -> IntMap c)
-> (IntMap a -> IntMap b -> IntMap c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
mergeWithKey' Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' IntMap a -> IntMap b -> IntMap c
f IntMap a -> IntMap c
g1 IntMap b -> IntMap c
g2 = IntMap a -> IntMap b -> IntMap c
go
where
go :: IntMap a -> IntMap b -> IntMap c
go t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) t2 :: IntMap b
t2@(Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
| Key -> Key -> Bool
shorter Key
m1 Key
m2 = IntMap c
merge1
| Key -> Key -> Bool
shorter Key
m2 Key
m1 = IntMap c
merge2
| Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2 = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p1 Key
m1 (IntMap a -> IntMap b -> IntMap c
go IntMap a
l1 IntMap b
l2) (IntMap a -> IntMap b -> IntMap c
go IntMap a
r1 IntMap b
r2)
| Bool
otherwise = Key -> IntMap c -> Key -> IntMap c -> IntMap c
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
p1 (IntMap a -> IntMap c
g1 IntMap a
t1) Key
p2 (IntMap b -> IntMap c
g2 IntMap b
t2)
where
merge1 :: IntMap c
merge1 | Key -> Key -> Key -> Bool
nomatch Key
p2 Key
p1 Key
m1 = Key -> IntMap c -> Key -> IntMap c -> IntMap c
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
p1 (IntMap a -> IntMap c
g1 IntMap a
t1) Key
p2 (IntMap b -> IntMap c
g2 IntMap b
t2)
| Key -> Key -> Bool
zero Key
p2 Key
m1 = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p1 Key
m1 (IntMap a -> IntMap b -> IntMap c
go IntMap a
l1 IntMap b
t2) (IntMap a -> IntMap c
g1 IntMap a
r1)
| Bool
otherwise = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p1 Key
m1 (IntMap a -> IntMap c
g1 IntMap a
l1) (IntMap a -> IntMap b -> IntMap c
go IntMap a
r1 IntMap b
t2)
merge2 :: IntMap c
merge2 | Key -> Key -> Key -> Bool
nomatch Key
p1 Key
p2 Key
m2 = Key -> IntMap c -> Key -> IntMap c -> IntMap c
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
p1 (IntMap a -> IntMap c
g1 IntMap a
t1) Key
p2 (IntMap b -> IntMap c
g2 IntMap b
t2)
| Key -> Key -> Bool
zero Key
p1 Key
m2 = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p2 Key
m2 (IntMap a -> IntMap b -> IntMap c
go IntMap a
t1 IntMap b
l2) (IntMap b -> IntMap c
g2 IntMap b
r2)
| Bool
otherwise = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p2 Key
m2 (IntMap b -> IntMap c
g2 IntMap b
l2) (IntMap a -> IntMap b -> IntMap c
go IntMap a
t1 IntMap b
r2)
go t1' :: IntMap a
t1'@(Bin Key
_ Key
_ IntMap a
_ IntMap a
_) t2' :: IntMap b
t2'@(Tip Key
k2' b
_) = IntMap b -> Key -> IntMap a -> IntMap c
merge0 IntMap b
t2' Key
k2' IntMap a
t1'
where
merge0 :: IntMap b -> Key -> IntMap a -> IntMap c
merge0 IntMap b
t2 Key
k2 t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1)
| Key -> Key -> Key -> Bool
nomatch Key
k2 Key
p1 Key
m1 = Key -> IntMap c -> Key -> IntMap c -> IntMap c
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
p1 (IntMap a -> IntMap c
g1 IntMap a
t1) Key
k2 (IntMap b -> IntMap c
g2 IntMap b
t2)
| Key -> Key -> Bool
zero Key
k2 Key
m1 = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p1 Key
m1 (IntMap b -> Key -> IntMap a -> IntMap c
merge0 IntMap b
t2 Key
k2 IntMap a
l1) (IntMap a -> IntMap c
g1 IntMap a
r1)
| Bool
otherwise = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p1 Key
m1 (IntMap a -> IntMap c
g1 IntMap a
l1) (IntMap b -> Key -> IntMap a -> IntMap c
merge0 IntMap b
t2 Key
k2 IntMap a
r1)
merge0 IntMap b
t2 Key
k2 t1 :: IntMap a
t1@(Tip Key
k1 a
_)
| Key
k1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
k2 = IntMap a -> IntMap b -> IntMap c
f IntMap a
t1 IntMap b
t2
| Bool
otherwise = Key -> IntMap c -> Key -> IntMap c -> IntMap c
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
k1 (IntMap a -> IntMap c
g1 IntMap a
t1) Key
k2 (IntMap b -> IntMap c
g2 IntMap b
t2)
merge0 IntMap b
t2 Key
_ IntMap a
Nil = IntMap b -> IntMap c
g2 IntMap b
t2
go t1 :: IntMap a
t1@(Bin Key
_ Key
_ IntMap a
_ IntMap a
_) IntMap b
Nil = IntMap a -> IntMap c
g1 IntMap a
t1
go t1' :: IntMap a
t1'@(Tip Key
k1' a
_) IntMap b
t2' = IntMap a -> Key -> IntMap b -> IntMap c
merge0 IntMap a
t1' Key
k1' IntMap b
t2'
where
merge0 :: IntMap a -> Key -> IntMap b -> IntMap c
merge0 IntMap a
t1 Key
k1 t2 :: IntMap b
t2@(Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
| Key -> Key -> Key -> Bool
nomatch Key
k1 Key
p2 Key
m2 = Key -> IntMap c -> Key -> IntMap c -> IntMap c
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
k1 (IntMap a -> IntMap c
g1 IntMap a
t1) Key
p2 (IntMap b -> IntMap c
g2 IntMap b
t2)
| Key -> Key -> Bool
zero Key
k1 Key
m2 = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p2 Key
m2 (IntMap a -> Key -> IntMap b -> IntMap c
merge0 IntMap a
t1 Key
k1 IntMap b
l2) (IntMap b -> IntMap c
g2 IntMap b
r2)
| Bool
otherwise = Key -> Key -> IntMap c -> IntMap c -> IntMap c
bin' Key
p2 Key
m2 (IntMap b -> IntMap c
g2 IntMap b
l2) (IntMap a -> Key -> IntMap b -> IntMap c
merge0 IntMap a
t1 Key
k1 IntMap b
r2)
merge0 IntMap a
t1 Key
k1 t2 :: IntMap b
t2@(Tip Key
k2 b
_)
| Key
k1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
k2 = IntMap a -> IntMap b -> IntMap c
f IntMap a
t1 IntMap b
t2
| Bool
otherwise = Key -> IntMap c -> Key -> IntMap c -> IntMap c
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
k1 (IntMap a -> IntMap c
g1 IntMap a
t1) Key
k2 (IntMap b -> IntMap c
g2 IntMap b
t2)
merge0 IntMap a
t1 Key
_ IntMap b
Nil = IntMap a -> IntMap c
g1 IntMap a
t1
go IntMap a
Nil IntMap b
t2 = IntMap b -> IntMap c
g2 IntMap b
t2
maybe_link :: Key -> IntMap a -> Key -> IntMap a -> IntMap a
maybe_link Key
_ IntMap a
Nil Key
_ IntMap a
t2 = IntMap a
t2
maybe_link Key
_ IntMap a
t1 Key
_ IntMap a
Nil = IntMap a
t1
maybe_link Key
p1 IntMap a
t1 Key
p2 IntMap a
t2 = Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
p1 IntMap a
t1 Key
p2 IntMap a
t2
{-# INLINE maybe_link #-}
{-# INLINE mergeWithKey' #-}
data WhenMissing f x y = WhenMissing
{ WhenMissing f x y -> IntMap x -> f (IntMap y)
missingSubtree :: IntMap x -> f (IntMap y)
, WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey :: Key -> x -> f (Maybe y)}
instance (Applicative f, Monad f) => Functor (WhenMissing f x) where
fmap :: (a -> b) -> WhenMissing f x a -> WhenMissing f x b
fmap = (a -> b) -> WhenMissing f x a -> WhenMissing f x b
forall (f :: * -> *) a b x.
(Applicative f, Monad f) =>
(a -> b) -> WhenMissing f x a -> WhenMissing f x b
mapWhenMissing
{-# INLINE fmap #-}
instance (Applicative f, Monad f) => Category.Category (WhenMissing f)
where
id :: WhenMissing f a a
id = WhenMissing f a a
forall (f :: * -> *) x. Applicative f => WhenMissing f x x
preserveMissing
WhenMissing f b c
f . :: WhenMissing f b c -> WhenMissing f a b -> WhenMissing f a c
. WhenMissing f a b
g =
(Key -> a -> f (Maybe c)) -> WhenMissing f a c
forall (f :: * -> *) x y.
Applicative f =>
(Key -> x -> f (Maybe y)) -> WhenMissing f x y
traverseMaybeMissing ((Key -> a -> f (Maybe c)) -> WhenMissing f a c)
-> (Key -> a -> f (Maybe c)) -> WhenMissing f a c
forall a b. (a -> b) -> a -> b
$ \ Key
k a
x -> do
Maybe b
y <- WhenMissing f a b -> Key -> a -> f (Maybe b)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f a b
g Key
k a
x
case Maybe b
y of
Maybe b
Nothing -> Maybe c -> f (Maybe c)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe c
forall a. Maybe a
Nothing
Just b
q -> WhenMissing f b c -> Key -> b -> f (Maybe c)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f b c
f Key
k b
q
{-# INLINE id #-}
{-# INLINE (.) #-}
instance (Applicative f, Monad f) => Applicative (WhenMissing f x) where
pure :: a -> WhenMissing f x a
pure a
x = (Key -> x -> a) -> WhenMissing f x a
forall (f :: * -> *) x y.
Applicative f =>
(Key -> x -> y) -> WhenMissing f x y
mapMissing (\ Key
_ x
_ -> a
x)
WhenMissing f x (a -> b)
f <*> :: WhenMissing f x (a -> b) -> WhenMissing f x a -> WhenMissing f x b
<*> WhenMissing f x a
g =
(Key -> x -> f (Maybe b)) -> WhenMissing f x b
forall (f :: * -> *) x y.
Applicative f =>
(Key -> x -> f (Maybe y)) -> WhenMissing f x y
traverseMaybeMissing ((Key -> x -> f (Maybe b)) -> WhenMissing f x b)
-> (Key -> x -> f (Maybe b)) -> WhenMissing f x b
forall a b. (a -> b) -> a -> b
$ \Key
k x
x -> do
Maybe (a -> b)
res1 <- WhenMissing f x (a -> b) -> Key -> x -> f (Maybe (a -> b))
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f x (a -> b)
f Key
k x
x
case Maybe (a -> b)
res1 of
Maybe (a -> b)
Nothing -> Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe b
forall a. Maybe a
Nothing
Just a -> b
r -> (Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe b -> f (Maybe b)) -> Maybe b -> f (Maybe b)
forall a b. (a -> b) -> a -> b
$!) (Maybe b -> f (Maybe b))
-> (Maybe a -> Maybe b) -> Maybe a -> f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
r (Maybe a -> f (Maybe b)) -> f (Maybe a) -> f (Maybe b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< WhenMissing f x a -> Key -> x -> f (Maybe a)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f x a
g Key
k x
x
{-# INLINE pure #-}
{-# INLINE (<*>) #-}
instance (Applicative f, Monad f) => Monad (WhenMissing f x) where
#if !MIN_VERSION_base(4,8,0)
return = pure
#endif
WhenMissing f x a
m >>= :: WhenMissing f x a -> (a -> WhenMissing f x b) -> WhenMissing f x b
>>= a -> WhenMissing f x b
f =
(Key -> x -> f (Maybe b)) -> WhenMissing f x b
forall (f :: * -> *) x y.
Applicative f =>
(Key -> x -> f (Maybe y)) -> WhenMissing f x y
traverseMaybeMissing ((Key -> x -> f (Maybe b)) -> WhenMissing f x b)
-> (Key -> x -> f (Maybe b)) -> WhenMissing f x b
forall a b. (a -> b) -> a -> b
$ \Key
k x
x -> do
Maybe a
res1 <- WhenMissing f x a -> Key -> x -> f (Maybe a)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f x a
m Key
k x
x
case Maybe a
res1 of
Maybe a
Nothing -> Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe b
forall a. Maybe a
Nothing
Just a
r -> WhenMissing f x b -> Key -> x -> f (Maybe b)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey (a -> WhenMissing f x b
f a
r) Key
k x
x
{-# INLINE (>>=) #-}
mapWhenMissing
:: (Applicative f, Monad f)
=> (a -> b)
-> WhenMissing f x a
-> WhenMissing f x b
mapWhenMissing :: (a -> b) -> WhenMissing f x a -> WhenMissing f x b
mapWhenMissing a -> b
f WhenMissing f x a
t = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap b)
missingSubtree = \IntMap x
m -> WhenMissing f x a -> IntMap x -> f (IntMap a)
forall (f :: * -> *) x y.
WhenMissing f x y -> IntMap x -> f (IntMap y)
missingSubtree WhenMissing f x a
t IntMap x
m f (IntMap a) -> (IntMap a -> f (IntMap b)) -> f (IntMap b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \IntMap a
m' -> IntMap b -> f (IntMap b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IntMap b -> f (IntMap b)) -> IntMap b -> f (IntMap b)
forall a b. (a -> b) -> a -> b
$! (a -> b) -> IntMap a -> IntMap b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f IntMap a
m'
, missingKey :: Key -> x -> f (Maybe b)
missingKey = \Key
k x
x -> WhenMissing f x a -> Key -> x -> f (Maybe a)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f x a
t Key
k x
x f (Maybe a) -> (Maybe a -> f (Maybe b)) -> f (Maybe b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Maybe a
q -> (Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe b -> f (Maybe b)) -> Maybe b -> f (Maybe b)
forall a b. (a -> b) -> a -> b
$! (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f Maybe a
q) }
{-# INLINE mapWhenMissing #-}
mapGentlyWhenMissing
:: Functor f
=> (a -> b)
-> WhenMissing f x a
-> WhenMissing f x b
mapGentlyWhenMissing :: (a -> b) -> WhenMissing f x a -> WhenMissing f x b
mapGentlyWhenMissing a -> b
f WhenMissing f x a
t = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap b)
missingSubtree = \IntMap x
m -> (a -> b) -> IntMap a -> IntMap b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (IntMap a -> IntMap b) -> f (IntMap a) -> f (IntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WhenMissing f x a -> IntMap x -> f (IntMap a)
forall (f :: * -> *) x y.
WhenMissing f x y -> IntMap x -> f (IntMap y)
missingSubtree WhenMissing f x a
t IntMap x
m
, missingKey :: Key -> x -> f (Maybe b)
missingKey = \Key
k x
x -> (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Maybe a -> Maybe b) -> f (Maybe a) -> f (Maybe b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WhenMissing f x a -> Key -> x -> f (Maybe a)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f x a
t Key
k x
x }
{-# INLINE mapGentlyWhenMissing #-}
mapGentlyWhenMatched
:: Functor f
=> (a -> b)
-> WhenMatched f x y a
-> WhenMatched f x y b
mapGentlyWhenMatched :: (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b
mapGentlyWhenMatched a -> b
f WhenMatched f x y a
t =
(Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall x y (f :: * -> *) z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
zipWithMaybeAMatched ((Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b)
-> (Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall a b. (a -> b) -> a -> b
$ \Key
k x
x y
y -> (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f (Maybe a -> Maybe b) -> f (Maybe a) -> f (Maybe b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> WhenMatched f x y a -> Key -> x -> y -> f (Maybe a)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f x y a
t Key
k x
x y
y
{-# INLINE mapGentlyWhenMatched #-}
lmapWhenMissing :: (b -> a) -> WhenMissing f a x -> WhenMissing f b x
lmapWhenMissing :: (b -> a) -> WhenMissing f a x -> WhenMissing f b x
lmapWhenMissing b -> a
f WhenMissing f a x
t = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap b -> f (IntMap x)
missingSubtree = \IntMap b
m -> WhenMissing f a x -> IntMap a -> f (IntMap x)
forall (f :: * -> *) x y.
WhenMissing f x y -> IntMap x -> f (IntMap y)
missingSubtree WhenMissing f a x
t ((b -> a) -> IntMap b -> IntMap a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap b -> a
f IntMap b
m)
, missingKey :: Key -> b -> f (Maybe x)
missingKey = \Key
k b
x -> WhenMissing f a x -> Key -> a -> f (Maybe x)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey WhenMissing f a x
t Key
k (b -> a
f b
x) }
{-# INLINE lmapWhenMissing #-}
contramapFirstWhenMatched
:: (b -> a)
-> WhenMatched f a y z
-> WhenMatched f b y z
contramapFirstWhenMatched :: (b -> a) -> WhenMatched f a y z -> WhenMatched f b y z
contramapFirstWhenMatched b -> a
f WhenMatched f a y z
t =
(Key -> b -> y -> f (Maybe z)) -> WhenMatched f b y z
forall (f :: * -> *) x y z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
WhenMatched ((Key -> b -> y -> f (Maybe z)) -> WhenMatched f b y z)
-> (Key -> b -> y -> f (Maybe z)) -> WhenMatched f b y z
forall a b. (a -> b) -> a -> b
$ \Key
k b
x y
y -> WhenMatched f a y z -> Key -> a -> y -> f (Maybe z)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f a y z
t Key
k (b -> a
f b
x) y
y
{-# INLINE contramapFirstWhenMatched #-}
contramapSecondWhenMatched
:: (b -> a)
-> WhenMatched f x a z
-> WhenMatched f x b z
contramapSecondWhenMatched :: (b -> a) -> WhenMatched f x a z -> WhenMatched f x b z
contramapSecondWhenMatched b -> a
f WhenMatched f x a z
t =
(Key -> x -> b -> f (Maybe z)) -> WhenMatched f x b z
forall (f :: * -> *) x y z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
WhenMatched ((Key -> x -> b -> f (Maybe z)) -> WhenMatched f x b z)
-> (Key -> x -> b -> f (Maybe z)) -> WhenMatched f x b z
forall a b. (a -> b) -> a -> b
$ \Key
k x
x b
y -> WhenMatched f x a z -> Key -> x -> a -> f (Maybe z)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f x a z
t Key
k x
x (b -> a
f b
y)
{-# INLINE contramapSecondWhenMatched #-}
#if !MIN_VERSION_base(4,8,0)
newtype Identity a = Identity {runIdentity :: a}
instance Functor Identity where
fmap f (Identity x) = Identity (f x)
instance Applicative Identity where
pure = Identity
Identity f <*> Identity x = Identity (f x)
#endif
type SimpleWhenMissing = WhenMissing Identity
newtype WhenMatched f x y z = WhenMatched
{ WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
matchedKey :: Key -> x -> y -> f (Maybe z) }
runWhenMatched :: WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched :: WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched = WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
matchedKey
{-# INLINE runWhenMatched #-}
runWhenMissing :: WhenMissing f x y -> Key-> x -> f (Maybe y)
runWhenMissing :: WhenMissing f x y -> Key -> x -> f (Maybe y)
runWhenMissing = WhenMissing f x y -> Key -> x -> f (Maybe y)
forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey
{-# INLINE runWhenMissing #-}
instance Functor f => Functor (WhenMatched f x y) where
fmap :: (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b
fmap = (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b
forall (f :: * -> *) a b x y.
Functor f =>
(a -> b) -> WhenMatched f x y a -> WhenMatched f x y b
mapWhenMatched
{-# INLINE fmap #-}
instance (Monad f, Applicative f) => Category.Category (WhenMatched f x)
where
id :: WhenMatched f x a a
id = (Key -> x -> a -> a) -> WhenMatched f x a a
forall (f :: * -> *) x y z.
Applicative f =>
(Key -> x -> y -> z) -> WhenMatched f x y z
zipWithMatched (\Key
_ x
_ a
y -> a
y)
WhenMatched f x b c
f . :: WhenMatched f x b c -> WhenMatched f x a b -> WhenMatched f x a c
. WhenMatched f x a b
g =
(Key -> x -> a -> f (Maybe c)) -> WhenMatched f x a c
forall x y (f :: * -> *) z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
zipWithMaybeAMatched ((Key -> x -> a -> f (Maybe c)) -> WhenMatched f x a c)
-> (Key -> x -> a -> f (Maybe c)) -> WhenMatched f x a c
forall a b. (a -> b) -> a -> b
$ \Key
k x
x a
y -> do
Maybe b
res <- WhenMatched f x a b -> Key -> x -> a -> f (Maybe b)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f x a b
g Key
k x
x a
y
case Maybe b
res of
Maybe b
Nothing -> Maybe c -> f (Maybe c)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe c
forall a. Maybe a
Nothing
Just b
r -> WhenMatched f x b c -> Key -> x -> b -> f (Maybe c)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f x b c
f Key
k x
x b
r
{-# INLINE id #-}
{-# INLINE (.) #-}
instance (Monad f, Applicative f) => Applicative (WhenMatched f x y) where
pure :: a -> WhenMatched f x y a
pure a
x = (Key -> x -> y -> a) -> WhenMatched f x y a
forall (f :: * -> *) x y z.
Applicative f =>
(Key -> x -> y -> z) -> WhenMatched f x y z
zipWithMatched (\Key
_ x
_ y
_ -> a
x)
WhenMatched f x y (a -> b)
fs <*> :: WhenMatched f x y (a -> b)
-> WhenMatched f x y a -> WhenMatched f x y b
<*> WhenMatched f x y a
xs =
(Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall x y (f :: * -> *) z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
zipWithMaybeAMatched ((Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b)
-> (Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall a b. (a -> b) -> a -> b
$ \Key
k x
x y
y -> do
Maybe (a -> b)
res <- WhenMatched f x y (a -> b) -> Key -> x -> y -> f (Maybe (a -> b))
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f x y (a -> b)
fs Key
k x
x y
y
case Maybe (a -> b)
res of
Maybe (a -> b)
Nothing -> Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe b
forall a. Maybe a
Nothing
Just a -> b
r -> (Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe b -> f (Maybe b)) -> Maybe b -> f (Maybe b)
forall a b. (a -> b) -> a -> b
$!) (Maybe b -> f (Maybe b))
-> (Maybe a -> Maybe b) -> Maybe a -> f (Maybe b)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
r (Maybe a -> f (Maybe b)) -> f (Maybe a) -> f (Maybe b)
forall (m :: * -> *) a b. Monad m => (a -> m b) -> m a -> m b
=<< WhenMatched f x y a -> Key -> x -> y -> f (Maybe a)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f x y a
xs Key
k x
x y
y
{-# INLINE pure #-}
{-# INLINE (<*>) #-}
instance (Monad f, Applicative f) => Monad (WhenMatched f x y) where
#if !MIN_VERSION_base(4,8,0)
return = pure
#endif
WhenMatched f x y a
m >>= :: WhenMatched f x y a
-> (a -> WhenMatched f x y b) -> WhenMatched f x y b
>>= a -> WhenMatched f x y b
f =
(Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall x y (f :: * -> *) z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
zipWithMaybeAMatched ((Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b)
-> (Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall a b. (a -> b) -> a -> b
$ \Key
k x
x y
y -> do
Maybe a
res <- WhenMatched f x y a -> Key -> x -> y -> f (Maybe a)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f x y a
m Key
k x
x y
y
case Maybe a
res of
Maybe a
Nothing -> Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe b
forall a. Maybe a
Nothing
Just a
r -> WhenMatched f x y b -> Key -> x -> y -> f (Maybe b)
forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
runWhenMatched (a -> WhenMatched f x y b
f a
r) Key
k x
x y
y
{-# INLINE (>>=) #-}
mapWhenMatched
:: Functor f
=> (a -> b)
-> WhenMatched f x y a
-> WhenMatched f x y b
mapWhenMatched :: (a -> b) -> WhenMatched f x y a -> WhenMatched f x y b
mapWhenMatched a -> b
f (WhenMatched Key -> x -> y -> f (Maybe a)
g) =
(Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall (f :: * -> *) x y z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
WhenMatched ((Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b)
-> (Key -> x -> y -> f (Maybe b)) -> WhenMatched f x y b
forall a b. (a -> b) -> a -> b
$ \Key
k x
x y
y -> (Maybe a -> Maybe b) -> f (Maybe a) -> f (Maybe b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f) (Key -> x -> y -> f (Maybe a)
g Key
k x
x y
y)
{-# INLINE mapWhenMatched #-}
type SimpleWhenMatched = WhenMatched Identity
zipWithMatched
:: Applicative f
=> (Key -> x -> y -> z)
-> WhenMatched f x y z
zipWithMatched :: (Key -> x -> y -> z) -> WhenMatched f x y z
zipWithMatched Key -> x -> y -> z
f = (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall (f :: * -> *) x y z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
WhenMatched ((Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z)
-> (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall a b. (a -> b) -> a -> b
$ \ Key
k x
x y
y -> Maybe z -> f (Maybe z)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe z -> f (Maybe z)) -> (z -> Maybe z) -> z -> f (Maybe z)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. z -> Maybe z
forall a. a -> Maybe a
Just (z -> f (Maybe z)) -> z -> f (Maybe z)
forall a b. (a -> b) -> a -> b
$ Key -> x -> y -> z
f Key
k x
x y
y
{-# INLINE zipWithMatched #-}
zipWithAMatched
:: Applicative f
=> (Key -> x -> y -> f z)
-> WhenMatched f x y z
zipWithAMatched :: (Key -> x -> y -> f z) -> WhenMatched f x y z
zipWithAMatched Key -> x -> y -> f z
f = (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall (f :: * -> *) x y z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
WhenMatched ((Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z)
-> (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall a b. (a -> b) -> a -> b
$ \ Key
k x
x y
y -> z -> Maybe z
forall a. a -> Maybe a
Just (z -> Maybe z) -> f z -> f (Maybe z)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> x -> y -> f z
f Key
k x
x y
y
{-# INLINE zipWithAMatched #-}
zipWithMaybeMatched
:: Applicative f
=> (Key -> x -> y -> Maybe z)
-> WhenMatched f x y z
zipWithMaybeMatched :: (Key -> x -> y -> Maybe z) -> WhenMatched f x y z
zipWithMaybeMatched Key -> x -> y -> Maybe z
f = (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall (f :: * -> *) x y z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
WhenMatched ((Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z)
-> (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall a b. (a -> b) -> a -> b
$ \ Key
k x
x y
y -> Maybe z -> f (Maybe z)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe z -> f (Maybe z)) -> Maybe z -> f (Maybe z)
forall a b. (a -> b) -> a -> b
$ Key -> x -> y -> Maybe z
f Key
k x
x y
y
{-# INLINE zipWithMaybeMatched #-}
zipWithMaybeAMatched
:: (Key -> x -> y -> f (Maybe z))
-> WhenMatched f x y z
zipWithMaybeAMatched :: (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
zipWithMaybeAMatched Key -> x -> y -> f (Maybe z)
f = (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall (f :: * -> *) x y z.
(Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
WhenMatched ((Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z)
-> (Key -> x -> y -> f (Maybe z)) -> WhenMatched f x y z
forall a b. (a -> b) -> a -> b
$ \ Key
k x
x y
y -> Key -> x -> y -> f (Maybe z)
f Key
k x
x y
y
{-# INLINE zipWithMaybeAMatched #-}
dropMissing :: Applicative f => WhenMissing f x y
dropMissing :: WhenMissing f x y
dropMissing = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap y)
missingSubtree = f (IntMap y) -> IntMap x -> f (IntMap y)
forall a b. a -> b -> a
const (IntMap y -> f (IntMap y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure IntMap y
forall a. IntMap a
Nil)
, missingKey :: Key -> x -> f (Maybe y)
missingKey = \Key
_ x
_ -> Maybe y -> f (Maybe y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Maybe y
forall a. Maybe a
Nothing }
{-# INLINE dropMissing #-}
preserveMissing :: Applicative f => WhenMissing f x x
preserveMissing :: WhenMissing f x x
preserveMissing = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap x)
missingSubtree = IntMap x -> f (IntMap x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
, missingKey :: Key -> x -> f (Maybe x)
missingKey = \Key
_ x
v -> Maybe x -> f (Maybe x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (x -> Maybe x
forall a. a -> Maybe a
Just x
v) }
{-# INLINE preserveMissing #-}
mapMissing :: Applicative f => (Key -> x -> y) -> WhenMissing f x y
mapMissing :: (Key -> x -> y) -> WhenMissing f x y
mapMissing Key -> x -> y
f = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap y)
missingSubtree = \IntMap x
m -> IntMap y -> f (IntMap y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IntMap y -> f (IntMap y)) -> IntMap y -> f (IntMap y)
forall a b. (a -> b) -> a -> b
$! (Key -> x -> y) -> IntMap x -> IntMap y
forall a b. (Key -> a -> b) -> IntMap a -> IntMap b
mapWithKey Key -> x -> y
f IntMap x
m
, missingKey :: Key -> x -> f (Maybe y)
missingKey = \Key
k x
x -> Maybe y -> f (Maybe y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe y -> f (Maybe y)) -> Maybe y -> f (Maybe y)
forall a b. (a -> b) -> a -> b
$ y -> Maybe y
forall a. a -> Maybe a
Just (Key -> x -> y
f Key
k x
x) }
{-# INLINE mapMissing #-}
mapMaybeMissing
:: Applicative f => (Key -> x -> Maybe y) -> WhenMissing f x y
mapMaybeMissing :: (Key -> x -> Maybe y) -> WhenMissing f x y
mapMaybeMissing Key -> x -> Maybe y
f = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap y)
missingSubtree = \IntMap x
m -> IntMap y -> f (IntMap y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IntMap y -> f (IntMap y)) -> IntMap y -> f (IntMap y)
forall a b. (a -> b) -> a -> b
$! (Key -> x -> Maybe y) -> IntMap x -> IntMap y
forall a b. (Key -> a -> Maybe b) -> IntMap a -> IntMap b
mapMaybeWithKey Key -> x -> Maybe y
f IntMap x
m
, missingKey :: Key -> x -> f (Maybe y)
missingKey = \Key
k x
x -> Maybe y -> f (Maybe y)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe y -> f (Maybe y)) -> Maybe y -> f (Maybe y)
forall a b. (a -> b) -> a -> b
$! Key -> x -> Maybe y
f Key
k x
x }
{-# INLINE mapMaybeMissing #-}
filterMissing
:: Applicative f => (Key -> x -> Bool) -> WhenMissing f x x
filterMissing :: (Key -> x -> Bool) -> WhenMissing f x x
filterMissing Key -> x -> Bool
f = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap x)
missingSubtree = \IntMap x
m -> IntMap x -> f (IntMap x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IntMap x -> f (IntMap x)) -> IntMap x -> f (IntMap x)
forall a b. (a -> b) -> a -> b
$! (Key -> x -> Bool) -> IntMap x -> IntMap x
forall a. (Key -> a -> Bool) -> IntMap a -> IntMap a
filterWithKey Key -> x -> Bool
f IntMap x
m
, missingKey :: Key -> x -> f (Maybe x)
missingKey = \Key
k x
x -> Maybe x -> f (Maybe x)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Maybe x -> f (Maybe x)) -> Maybe x -> f (Maybe x)
forall a b. (a -> b) -> a -> b
$! if Key -> x -> Bool
f Key
k x
x then x -> Maybe x
forall a. a -> Maybe a
Just x
x else Maybe x
forall a. Maybe a
Nothing }
{-# INLINE filterMissing #-}
filterAMissing
:: Applicative f => (Key -> x -> f Bool) -> WhenMissing f x x
filterAMissing :: (Key -> x -> f Bool) -> WhenMissing f x x
filterAMissing Key -> x -> f Bool
f = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap x)
missingSubtree = \IntMap x
m -> (Key -> x -> f Bool) -> IntMap x -> f (IntMap x)
forall (f :: * -> *) a.
Applicative f =>
(Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
filterWithKeyA Key -> x -> f Bool
f IntMap x
m
, missingKey :: Key -> x -> f (Maybe x)
missingKey = \Key
k x
x -> Maybe x -> Maybe x -> Bool -> Maybe x
forall a. a -> a -> Bool -> a
bool Maybe x
forall a. Maybe a
Nothing (x -> Maybe x
forall a. a -> Maybe a
Just x
x) (Bool -> Maybe x) -> f Bool -> f (Maybe x)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> x -> f Bool
f Key
k x
x }
{-# INLINE filterAMissing #-}
filterWithKeyA
:: Applicative f => (Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
filterWithKeyA :: (Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
filterWithKeyA Key -> a -> f Bool
_ IntMap a
Nil = IntMap a -> f (IntMap a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure IntMap a
forall a. IntMap a
Nil
filterWithKeyA Key -> a -> f Bool
f t :: IntMap a
t@(Tip Key
k a
x) = (\Bool
b -> if Bool
b then IntMap a
t else IntMap a
forall a. IntMap a
Nil) (Bool -> IntMap a) -> f Bool -> f (IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> f Bool
f Key
k a
x
filterWithKeyA Key -> a -> f Bool
f (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = (IntMap a -> IntMap a -> IntMap a)
-> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((IntMap a -> IntMap a -> IntMap a)
-> IntMap a -> IntMap a -> IntMap a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m)) ((Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
forall (f :: * -> *) a.
Applicative f =>
(Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
filterWithKeyA Key -> a -> f Bool
f IntMap a
r) ((Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
forall (f :: * -> *) a.
Applicative f =>
(Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
filterWithKeyA Key -> a -> f Bool
f IntMap a
l)
| Bool
otherwise = (IntMap a -> IntMap a -> IntMap a)
-> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m) ((Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
forall (f :: * -> *) a.
Applicative f =>
(Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
filterWithKeyA Key -> a -> f Bool
f IntMap a
l) ((Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
forall (f :: * -> *) a.
Applicative f =>
(Key -> a -> f Bool) -> IntMap a -> f (IntMap a)
filterWithKeyA Key -> a -> f Bool
f IntMap a
r)
bool :: a -> a -> Bool -> a
bool :: a -> a -> Bool -> a
bool a
f a
_ Bool
False = a
f
bool a
_ a
t Bool
True = a
t
traverseMissing
:: Applicative f => (Key -> x -> f y) -> WhenMissing f x y
traverseMissing :: (Key -> x -> f y) -> WhenMissing f x y
traverseMissing Key -> x -> f y
f = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap y)
missingSubtree = (Key -> x -> f y) -> IntMap x -> f (IntMap y)
forall (t :: * -> *) a b.
Applicative t =>
(Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseWithKey Key -> x -> f y
f
, missingKey :: Key -> x -> f (Maybe y)
missingKey = \Key
k x
x -> y -> Maybe y
forall a. a -> Maybe a
Just (y -> Maybe y) -> f y -> f (Maybe y)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> x -> f y
f Key
k x
x }
{-# INLINE traverseMissing #-}
traverseMaybeMissing
:: Applicative f => (Key -> x -> f (Maybe y)) -> WhenMissing f x y
traverseMaybeMissing :: (Key -> x -> f (Maybe y)) -> WhenMissing f x y
traverseMaybeMissing Key -> x -> f (Maybe y)
f = WhenMissing :: forall (f :: * -> *) x y.
(IntMap x -> f (IntMap y))
-> (Key -> x -> f (Maybe y)) -> WhenMissing f x y
WhenMissing
{ missingSubtree :: IntMap x -> f (IntMap y)
missingSubtree = (Key -> x -> f (Maybe y)) -> IntMap x -> f (IntMap y)
forall (f :: * -> *) a b.
Applicative f =>
(Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b)
traverseMaybeWithKey Key -> x -> f (Maybe y)
f
, missingKey :: Key -> x -> f (Maybe y)
missingKey = Key -> x -> f (Maybe y)
f }
{-# INLINE traverseMaybeMissing #-}
traverseMaybeWithKey
:: Applicative f => (Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b)
traverseMaybeWithKey :: (Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b)
traverseMaybeWithKey Key -> a -> f (Maybe b)
f = IntMap a -> f (IntMap b)
go
where
go :: IntMap a -> f (IntMap b)
go IntMap a
Nil = IntMap b -> f (IntMap b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure IntMap b
forall a. IntMap a
Nil
go (Tip Key
k a
x) = IntMap b -> (b -> IntMap b) -> Maybe b -> IntMap b
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap b
forall a. IntMap a
Nil (Key -> b -> IntMap b
forall a. Key -> a -> IntMap a
Tip Key
k) (Maybe b -> IntMap b) -> f (Maybe b) -> f (IntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> f (Maybe b)
f Key
k a
x
go (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = (IntMap b -> IntMap b -> IntMap b)
-> f (IntMap b) -> f (IntMap b) -> f (IntMap b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((IntMap b -> IntMap b -> IntMap b)
-> IntMap b -> IntMap b -> IntMap b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m)) (IntMap a -> f (IntMap b)
go IntMap a
r) (IntMap a -> f (IntMap b)
go IntMap a
l)
| Bool
otherwise = (IntMap b -> IntMap b -> IntMap b)
-> f (IntMap b) -> f (IntMap b) -> f (IntMap b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m) (IntMap a -> f (IntMap b)
go IntMap a
l) (IntMap a -> f (IntMap b)
go IntMap a
r)
merge
:: SimpleWhenMissing a c
-> SimpleWhenMissing b c
-> SimpleWhenMatched a b c
-> IntMap a
-> IntMap b
-> IntMap c
merge :: SimpleWhenMissing a c
-> SimpleWhenMissing b c
-> SimpleWhenMatched a b c
-> IntMap a
-> IntMap b
-> IntMap c
merge SimpleWhenMissing a c
g1 SimpleWhenMissing b c
g2 SimpleWhenMatched a b c
f IntMap a
m1 IntMap b
m2 =
Identity (IntMap c) -> IntMap c
forall a. Identity a -> a
runIdentity (Identity (IntMap c) -> IntMap c)
-> Identity (IntMap c) -> IntMap c
forall a b. (a -> b) -> a -> b
$ SimpleWhenMissing a c
-> SimpleWhenMissing b c
-> SimpleWhenMatched a b c
-> IntMap a
-> IntMap b
-> Identity (IntMap c)
forall (f :: * -> *) a c b.
Applicative f =>
WhenMissing f a c
-> WhenMissing f b c
-> WhenMatched f a b c
-> IntMap a
-> IntMap b
-> f (IntMap c)
mergeA SimpleWhenMissing a c
g1 SimpleWhenMissing b c
g2 SimpleWhenMatched a b c
f IntMap a
m1 IntMap b
m2
{-# INLINE merge #-}
mergeA
:: (Applicative f)
=> WhenMissing f a c
-> WhenMissing f b c
-> WhenMatched f a b c
-> IntMap a
-> IntMap b
-> f (IntMap c)
mergeA :: WhenMissing f a c
-> WhenMissing f b c
-> WhenMatched f a b c
-> IntMap a
-> IntMap b
-> f (IntMap c)
mergeA
WhenMissing{missingSubtree :: forall (f :: * -> *) x y.
WhenMissing f x y -> IntMap x -> f (IntMap y)
missingSubtree = IntMap a -> f (IntMap c)
g1t, missingKey :: forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey = Key -> a -> f (Maybe c)
g1k}
WhenMissing{missingSubtree :: forall (f :: * -> *) x y.
WhenMissing f x y -> IntMap x -> f (IntMap y)
missingSubtree = IntMap b -> f (IntMap c)
g2t, missingKey :: forall (f :: * -> *) x y.
WhenMissing f x y -> Key -> x -> f (Maybe y)
missingKey = Key -> b -> f (Maybe c)
g2k}
WhenMatched{matchedKey :: forall (f :: * -> *) x y z.
WhenMatched f x y z -> Key -> x -> y -> f (Maybe z)
matchedKey = Key -> a -> b -> f (Maybe c)
f}
= IntMap a -> IntMap b -> f (IntMap c)
go
where
go :: IntMap a -> IntMap b -> f (IntMap c)
go IntMap a
t1 IntMap b
Nil = IntMap a -> f (IntMap c)
g1t IntMap a
t1
go IntMap a
Nil IntMap b
t2 = IntMap b -> f (IntMap c)
g2t IntMap b
t2
go (Tip Key
k1 a
x1) IntMap b
t2' = IntMap b -> f (IntMap c)
merge2 IntMap b
t2'
where
merge2 :: IntMap b -> f (IntMap c)
merge2 t2 :: IntMap b
t2@(Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
| Key -> Key -> Key -> Bool
nomatch Key
k1 Key
p2 Key
m2 = Key -> f (IntMap c) -> Key -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> f (IntMap a) -> Key -> f (IntMap a) -> f (IntMap a)
linkA Key
k1 ((Key -> a -> f (Maybe c)) -> Key -> a -> f (IntMap c)
forall (f :: * -> *) t a.
Functor f =>
(Key -> t -> f (Maybe a)) -> Key -> t -> f (IntMap a)
subsingletonBy Key -> a -> f (Maybe c)
g1k Key
k1 a
x1) Key
p2 (IntMap b -> f (IntMap c)
g2t IntMap b
t2)
| Key -> Key -> Bool
zero Key
k1 Key
m2 = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p2 Key
m2 (IntMap b -> f (IntMap c)
merge2 IntMap b
l2) (IntMap b -> f (IntMap c)
g2t IntMap b
r2)
| Bool
otherwise = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p2 Key
m2 (IntMap b -> f (IntMap c)
g2t IntMap b
l2) (IntMap b -> f (IntMap c)
merge2 IntMap b
r2)
merge2 (Tip Key
k2 b
x2) = Key -> a -> Key -> b -> f (IntMap c)
mergeTips Key
k1 a
x1 Key
k2 b
x2
merge2 IntMap b
Nil = (Key -> a -> f (Maybe c)) -> Key -> a -> f (IntMap c)
forall (f :: * -> *) t a.
Functor f =>
(Key -> t -> f (Maybe a)) -> Key -> t -> f (IntMap a)
subsingletonBy Key -> a -> f (Maybe c)
g1k Key
k1 a
x1
go IntMap a
t1' (Tip Key
k2 b
x2) = IntMap a -> f (IntMap c)
merge1 IntMap a
t1'
where
merge1 :: IntMap a -> f (IntMap c)
merge1 t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1)
| Key -> Key -> Key -> Bool
nomatch Key
k2 Key
p1 Key
m1 = Key -> f (IntMap c) -> Key -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> f (IntMap a) -> Key -> f (IntMap a) -> f (IntMap a)
linkA Key
p1 (IntMap a -> f (IntMap c)
g1t IntMap a
t1) Key
k2 ((Key -> b -> f (Maybe c)) -> Key -> b -> f (IntMap c)
forall (f :: * -> *) t a.
Functor f =>
(Key -> t -> f (Maybe a)) -> Key -> t -> f (IntMap a)
subsingletonBy Key -> b -> f (Maybe c)
g2k Key
k2 b
x2)
| Key -> Key -> Bool
zero Key
k2 Key
m1 = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p1 Key
m1 (IntMap a -> f (IntMap c)
merge1 IntMap a
l1) (IntMap a -> f (IntMap c)
g1t IntMap a
r1)
| Bool
otherwise = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p1 Key
m1 (IntMap a -> f (IntMap c)
g1t IntMap a
l1) (IntMap a -> f (IntMap c)
merge1 IntMap a
r1)
merge1 (Tip Key
k1 a
x1) = Key -> a -> Key -> b -> f (IntMap c)
mergeTips Key
k1 a
x1 Key
k2 b
x2
merge1 IntMap a
Nil = (Key -> b -> f (Maybe c)) -> Key -> b -> f (IntMap c)
forall (f :: * -> *) t a.
Functor f =>
(Key -> t -> f (Maybe a)) -> Key -> t -> f (IntMap a)
subsingletonBy Key -> b -> f (Maybe c)
g2k Key
k2 b
x2
go t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) t2 :: IntMap b
t2@(Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
| Key -> Key -> Bool
shorter Key
m1 Key
m2 = f (IntMap c)
merge1
| Key -> Key -> Bool
shorter Key
m2 Key
m1 = f (IntMap c)
merge2
| Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2 = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p1 Key
m1 (IntMap a -> IntMap b -> f (IntMap c)
go IntMap a
l1 IntMap b
l2) (IntMap a -> IntMap b -> f (IntMap c)
go IntMap a
r1 IntMap b
r2)
| Bool
otherwise = Key -> f (IntMap c) -> Key -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> f (IntMap a) -> Key -> f (IntMap a) -> f (IntMap a)
linkA Key
p1 (IntMap a -> f (IntMap c)
g1t IntMap a
t1) Key
p2 (IntMap b -> f (IntMap c)
g2t IntMap b
t2)
where
merge1 :: f (IntMap c)
merge1 | Key -> Key -> Key -> Bool
nomatch Key
p2 Key
p1 Key
m1 = Key -> f (IntMap c) -> Key -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> f (IntMap a) -> Key -> f (IntMap a) -> f (IntMap a)
linkA Key
p1 (IntMap a -> f (IntMap c)
g1t IntMap a
t1) Key
p2 (IntMap b -> f (IntMap c)
g2t IntMap b
t2)
| Key -> Key -> Bool
zero Key
p2 Key
m1 = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p1 Key
m1 (IntMap a -> IntMap b -> f (IntMap c)
go IntMap a
l1 IntMap b
t2) (IntMap a -> f (IntMap c)
g1t IntMap a
r1)
| Bool
otherwise = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p1 Key
m1 (IntMap a -> f (IntMap c)
g1t IntMap a
l1) (IntMap a -> IntMap b -> f (IntMap c)
go IntMap a
r1 IntMap b
t2)
merge2 :: f (IntMap c)
merge2 | Key -> Key -> Key -> Bool
nomatch Key
p1 Key
p2 Key
m2 = Key -> f (IntMap c) -> Key -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> f (IntMap a) -> Key -> f (IntMap a) -> f (IntMap a)
linkA Key
p1 (IntMap a -> f (IntMap c)
g1t IntMap a
t1) Key
p2 (IntMap b -> f (IntMap c)
g2t IntMap b
t2)
| Key -> Key -> Bool
zero Key
p1 Key
m2 = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p2 Key
m2 (IntMap a -> IntMap b -> f (IntMap c)
go IntMap a
t1 IntMap b
l2) (IntMap b -> f (IntMap c)
g2t IntMap b
r2)
| Bool
otherwise = Key -> Key -> f (IntMap c) -> f (IntMap c) -> f (IntMap c)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p2 Key
m2 (IntMap b -> f (IntMap c)
g2t IntMap b
l2) (IntMap a -> IntMap b -> f (IntMap c)
go IntMap a
t1 IntMap b
r2)
subsingletonBy :: (Key -> t -> f (Maybe a)) -> Key -> t -> f (IntMap a)
subsingletonBy Key -> t -> f (Maybe a)
gk Key
k t
x = IntMap a -> (a -> IntMap a) -> Maybe a -> IntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap a
forall a. IntMap a
Nil (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k) (Maybe a -> IntMap a) -> f (Maybe a) -> f (IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> t -> f (Maybe a)
gk Key
k t
x
{-# INLINE subsingletonBy #-}
mergeTips :: Key -> a -> Key -> b -> f (IntMap c)
mergeTips Key
k1 a
x1 Key
k2 b
x2
| Key
k1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
k2 = IntMap c -> (c -> IntMap c) -> Maybe c -> IntMap c
forall b a. b -> (a -> b) -> Maybe a -> b
maybe IntMap c
forall a. IntMap a
Nil (Key -> c -> IntMap c
forall a. Key -> a -> IntMap a
Tip Key
k1) (Maybe c -> IntMap c) -> f (Maybe c) -> f (IntMap c)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> b -> f (Maybe c)
f Key
k1 a
x1 b
x2
| Key
k1 Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
k2 = (Maybe c -> Maybe c -> IntMap c)
-> f (Maybe c) -> f (Maybe c) -> f (IntMap c)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (Key -> Key -> Maybe c -> Maybe c -> IntMap c
forall a. Key -> Key -> Maybe a -> Maybe a -> IntMap a
subdoubleton Key
k1 Key
k2) (Key -> a -> f (Maybe c)
g1k Key
k1 a
x1) (Key -> b -> f (Maybe c)
g2k Key
k2 b
x2)
| Bool
otherwise = (Maybe c -> Maybe c -> IntMap c)
-> f (Maybe c) -> f (Maybe c) -> f (IntMap c)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (Key -> Key -> Maybe c -> Maybe c -> IntMap c
forall a. Key -> Key -> Maybe a -> Maybe a -> IntMap a
subdoubleton Key
k2 Key
k1) (Key -> b -> f (Maybe c)
g2k Key
k2 b
x2) (Key -> a -> f (Maybe c)
g1k Key
k1 a
x1)
{-# INLINE mergeTips #-}
subdoubleton :: Key -> Key -> Maybe a -> Maybe a -> IntMap a
subdoubleton Key
_ Key
_ Maybe a
Nothing Maybe a
Nothing = IntMap a
forall a. IntMap a
Nil
subdoubleton Key
_ Key
k2 Maybe a
Nothing (Just a
y2) = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k2 a
y2
subdoubleton Key
k1 Key
_ (Just a
y1) Maybe a
Nothing = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k1 a
y1
subdoubleton Key
k1 Key
k2 (Just a
y1) (Just a
y2) = Key -> IntMap a -> Key -> IntMap a -> IntMap a
forall a. Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
k1 (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k1 a
y1) Key
k2 (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k2 a
y2)
{-# INLINE subdoubleton #-}
linkA
:: Applicative f
=> Prefix -> f (IntMap a)
-> Prefix -> f (IntMap a)
-> f (IntMap a)
linkA :: Key -> f (IntMap a) -> Key -> f (IntMap a) -> f (IntMap a)
linkA Key
p1 f (IntMap a)
t1 Key
p2 f (IntMap a)
t2
| Key -> Key -> Bool
zero Key
p1 Key
m = Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p Key
m f (IntMap a)
t1 f (IntMap a)
t2
| Bool
otherwise = Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
forall (f :: * -> *) a.
Applicative f =>
Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p Key
m f (IntMap a)
t2 f (IntMap a)
t1
where
m :: Key
m = Key -> Key -> Key
branchMask Key
p1 Key
p2
p :: Key
p = Key -> Key -> Key
mask Key
p1 Key
m
{-# INLINE linkA #-}
binA
:: Applicative f
=> Prefix
-> Mask
-> f (IntMap a)
-> f (IntMap a)
-> f (IntMap a)
binA :: Key -> Key -> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
binA Key
p Key
m f (IntMap a)
a f (IntMap a)
b
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = (IntMap a -> IntMap a -> IntMap a)
-> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((IntMap a -> IntMap a -> IntMap a)
-> IntMap a -> IntMap a -> IntMap a
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m)) f (IntMap a)
b f (IntMap a)
a
| Bool
otherwise = (IntMap a -> IntMap a -> IntMap a)
-> f (IntMap a) -> f (IntMap a) -> f (IntMap a)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m) f (IntMap a)
a f (IntMap a)
b
{-# INLINE binA #-}
{-# INLINE mergeA #-}
updateMinWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a
updateMinWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a
updateMinWithKey Key -> a -> Maybe a
f IntMap a
t =
case IntMap a
t of Bin Key
p Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l ((Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall t. (Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> a -> Maybe a
f IntMap a
r)
IntMap a
_ -> (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall t. (Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> a -> Maybe a
f IntMap a
t
where
go :: (Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> t -> Maybe t
f' (Bin Key
p Key
m IntMap t
l IntMap t
r) = Key -> Key -> IntMap t -> IntMap t -> IntMap t
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m ((Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> t -> Maybe t
f' IntMap t
l) IntMap t
r
go Key -> t -> Maybe t
f' (Tip Key
k t
y) = case Key -> t -> Maybe t
f' Key
k t
y of
Just t
y' -> Key -> t -> IntMap t
forall a. Key -> a -> IntMap a
Tip Key
k t
y'
Maybe t
Nothing -> IntMap t
forall a. IntMap a
Nil
go Key -> t -> Maybe t
_ IntMap t
Nil = [Char] -> IntMap t
forall a. HasCallStack => [Char] -> a
error [Char]
"updateMinWithKey Nil"
updateMaxWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a
updateMaxWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a
updateMaxWithKey Key -> a -> Maybe a
f IntMap a
t =
case IntMap a
t of Bin Key
p Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m ((Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall t. (Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> a -> Maybe a
f IntMap a
l) IntMap a
r
IntMap a
_ -> (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall t. (Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> a -> Maybe a
f IntMap a
t
where
go :: (Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> t -> Maybe t
f' (Bin Key
p Key
m IntMap t
l IntMap t
r) = Key -> Key -> IntMap t -> IntMap t -> IntMap t
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap t
l ((Key -> t -> Maybe t) -> IntMap t -> IntMap t
go Key -> t -> Maybe t
f' IntMap t
r)
go Key -> t -> Maybe t
f' (Tip Key
k t
y) = case Key -> t -> Maybe t
f' Key
k t
y of
Just t
y' -> Key -> t -> IntMap t
forall a. Key -> a -> IntMap a
Tip Key
k t
y'
Maybe t
Nothing -> IntMap t
forall a. IntMap a
Nil
go Key -> t -> Maybe t
_ IntMap t
Nil = [Char] -> IntMap t
forall a. HasCallStack => [Char] -> a
error [Char]
"updateMaxWithKey Nil"
data View a = View {-# UNPACK #-} !Key a !(IntMap a)
maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a)
maxViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a)
maxViewWithKey IntMap a
t = case IntMap a
t of
IntMap a
Nil -> Maybe ((Key, a), IntMap a)
forall a. Maybe a
Nothing
IntMap a
_ -> ((Key, a), IntMap a) -> Maybe ((Key, a), IntMap a)
forall a. a -> Maybe a
Just (((Key, a), IntMap a) -> Maybe ((Key, a), IntMap a))
-> ((Key, a), IntMap a) -> Maybe ((Key, a), IntMap a)
forall a b. (a -> b) -> a -> b
$ case IntMap a -> View a
forall a. IntMap a -> View a
maxViewWithKeySure IntMap a
t of
View Key
k a
v IntMap a
t' -> ((Key
k, a
v), IntMap a
t')
{-# INLINE maxViewWithKey #-}
maxViewWithKeySure :: IntMap a -> View a
maxViewWithKeySure :: IntMap a -> View a
maxViewWithKeySure IntMap a
t =
case IntMap a
t of
IntMap a
Nil -> [Char] -> View a
forall a. HasCallStack => [Char] -> a
error [Char]
"maxViewWithKeySure Nil"
Bin Key
p Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 ->
case IntMap a -> View a
forall a. IntMap a -> View a
go IntMap a
l of View Key
k a
a IntMap a
l' -> Key -> a -> IntMap a -> View a
forall a. Key -> a -> IntMap a -> View a
View Key
k a
a (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m IntMap a
l' IntMap a
r)
IntMap a
_ -> IntMap a -> View a
forall a. IntMap a -> View a
go IntMap a
t
where
go :: IntMap a -> View a
go (Bin Key
p Key
m IntMap a
l IntMap a
r) =
case IntMap a -> View a
go IntMap a
r of View Key
k a
a IntMap a
r' -> Key -> a -> IntMap a -> View a
forall a. Key -> a -> IntMap a -> View a
View Key
k a
a (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l IntMap a
r')
go (Tip Key
k a
y) = Key -> a -> IntMap a -> View a
forall a. Key -> a -> IntMap a -> View a
View Key
k a
y IntMap a
forall a. IntMap a
Nil
go IntMap a
Nil = [Char] -> View a
forall a. HasCallStack => [Char] -> a
error [Char]
"maxViewWithKey_go Nil"
{-# NOINLINE maxViewWithKeySure #-}
minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a)
minViewWithKey :: IntMap a -> Maybe ((Key, a), IntMap a)
minViewWithKey IntMap a
t =
case IntMap a
t of
IntMap a
Nil -> Maybe ((Key, a), IntMap a)
forall a. Maybe a
Nothing
IntMap a
_ -> ((Key, a), IntMap a) -> Maybe ((Key, a), IntMap a)
forall a. a -> Maybe a
Just (((Key, a), IntMap a) -> Maybe ((Key, a), IntMap a))
-> ((Key, a), IntMap a) -> Maybe ((Key, a), IntMap a)
forall a b. (a -> b) -> a -> b
$ case IntMap a -> View a
forall a. IntMap a -> View a
minViewWithKeySure IntMap a
t of
View Key
k a
v IntMap a
t' -> ((Key
k, a
v), IntMap a
t')
{-# INLINE minViewWithKey #-}
minViewWithKeySure :: IntMap a -> View a
minViewWithKeySure :: IntMap a -> View a
minViewWithKeySure IntMap a
t =
case IntMap a
t of
IntMap a
Nil -> [Char] -> View a
forall a. HasCallStack => [Char] -> a
error [Char]
"minViewWithKeySure Nil"
Bin Key
p Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 ->
case IntMap a -> View a
forall a. IntMap a -> View a
go IntMap a
r of
View Key
k a
a IntMap a
r' -> Key -> a -> IntMap a -> View a
forall a. Key -> a -> IntMap a -> View a
View Key
k a
a (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
p Key
m IntMap a
l IntMap a
r')
IntMap a
_ -> IntMap a -> View a
forall a. IntMap a -> View a
go IntMap a
t
where
go :: IntMap a -> View a
go (Bin Key
p Key
m IntMap a
l IntMap a
r) =
case IntMap a -> View a
go IntMap a
l of View Key
k a
a IntMap a
l' -> Key -> a -> IntMap a -> View a
forall a. Key -> a -> IntMap a -> View a
View Key
k a
a (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
p Key
m IntMap a
l' IntMap a
r)
go (Tip Key
k a
y) = Key -> a -> IntMap a -> View a
forall a. Key -> a -> IntMap a -> View a
View Key
k a
y IntMap a
forall a. IntMap a
Nil
go IntMap a
Nil = [Char] -> View a
forall a. HasCallStack => [Char] -> a
error [Char]
"minViewWithKey_go Nil"
{-# NOINLINE minViewWithKeySure #-}
updateMax :: (a -> Maybe a) -> IntMap a -> IntMap a
updateMax :: (a -> Maybe a) -> IntMap a -> IntMap a
updateMax a -> Maybe a
f = (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall t. (Key -> t -> Maybe t) -> IntMap t -> IntMap t
updateMaxWithKey ((a -> Maybe a) -> Key -> a -> Maybe a
forall a b. a -> b -> a
const a -> Maybe a
f)
updateMin :: (a -> Maybe a) -> IntMap a -> IntMap a
updateMin :: (a -> Maybe a) -> IntMap a -> IntMap a
updateMin a -> Maybe a
f = (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall t. (Key -> t -> Maybe t) -> IntMap t -> IntMap t
updateMinWithKey ((a -> Maybe a) -> Key -> a -> Maybe a
forall a b. a -> b -> a
const a -> Maybe a
f)
maxView :: IntMap a -> Maybe (a, IntMap a)
maxView :: IntMap a -> Maybe (a, IntMap a)
maxView IntMap a
t = (((Key, a), IntMap a) -> (a, IntMap a))
-> Maybe ((Key, a), IntMap a) -> Maybe (a, IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\((Key
_, a
x), IntMap a
t') -> (a
x, IntMap a
t')) (IntMap a -> Maybe ((Key, a), IntMap a)
forall a. IntMap a -> Maybe ((Key, a), IntMap a)
maxViewWithKey IntMap a
t)
minView :: IntMap a -> Maybe (a, IntMap a)
minView :: IntMap a -> Maybe (a, IntMap a)
minView IntMap a
t = (((Key, a), IntMap a) -> (a, IntMap a))
-> Maybe ((Key, a), IntMap a) -> Maybe (a, IntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (\((Key
_, a
x), IntMap a
t') -> (a
x, IntMap a
t')) (IntMap a -> Maybe ((Key, a), IntMap a)
forall a. IntMap a -> Maybe ((Key, a), IntMap a)
minViewWithKey IntMap a
t)
deleteFindMax :: IntMap a -> ((Key, a), IntMap a)
deleteFindMax :: IntMap a -> ((Key, a), IntMap a)
deleteFindMax = ((Key, a), IntMap a)
-> Maybe ((Key, a), IntMap a) -> ((Key, a), IntMap a)
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> ((Key, a), IntMap a)
forall a. HasCallStack => [Char] -> a
error [Char]
"deleteFindMax: empty map has no maximal element") (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)
maxViewWithKey
deleteFindMin :: IntMap a -> ((Key, a), IntMap a)
deleteFindMin :: IntMap a -> ((Key, a), IntMap a)
deleteFindMin = ((Key, a), IntMap a)
-> Maybe ((Key, a), IntMap a) -> ((Key, a), IntMap a)
forall a. a -> Maybe a -> a
fromMaybe ([Char] -> ((Key, a), IntMap a)
forall a. HasCallStack => [Char] -> a
error [Char]
"deleteFindMin: empty map has no minimal element") (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)
minViewWithKey
lookupMin :: IntMap a -> Maybe (Key, a)
lookupMin :: IntMap a -> Maybe (Key, a)
lookupMin IntMap a
Nil = Maybe (Key, a)
forall a. Maybe a
Nothing
lookupMin (Tip Key
k a
v) = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k,a
v)
lookupMin (Bin Key
_ Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
go IntMap a
r
| Bool
otherwise = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
go IntMap a
l
where go :: IntMap b -> Maybe (Key, b)
go (Tip Key
k b
v) = (Key, b) -> Maybe (Key, b)
forall a. a -> Maybe a
Just (Key
k,b
v)
go (Bin Key
_ Key
_ IntMap b
l' IntMap b
_) = IntMap b -> Maybe (Key, b)
go IntMap b
l'
go IntMap b
Nil = Maybe (Key, b)
forall a. Maybe a
Nothing
findMin :: IntMap a -> (Key, a)
findMin :: IntMap a -> (Key, a)
findMin IntMap a
t
| Just (Key, a)
r <- IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
lookupMin IntMap a
t = (Key, a)
r
| Bool
otherwise = [Char] -> (Key, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"findMin: empty map has no minimal element"
lookupMax :: IntMap a -> Maybe (Key, a)
lookupMax :: IntMap a -> Maybe (Key, a)
lookupMax IntMap a
Nil = Maybe (Key, a)
forall a. Maybe a
Nothing
lookupMax (Tip Key
k a
v) = (Key, a) -> Maybe (Key, a)
forall a. a -> Maybe a
Just (Key
k,a
v)
lookupMax (Bin Key
_ Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
go IntMap a
l
| Bool
otherwise = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
go IntMap a
r
where go :: IntMap b -> Maybe (Key, b)
go (Tip Key
k b
v) = (Key, b) -> Maybe (Key, b)
forall a. a -> Maybe a
Just (Key
k,b
v)
go (Bin Key
_ Key
_ IntMap b
_ IntMap b
r') = IntMap b -> Maybe (Key, b)
go IntMap b
r'
go IntMap b
Nil = Maybe (Key, b)
forall a. Maybe a
Nothing
findMax :: IntMap a -> (Key, a)
findMax :: IntMap a -> (Key, a)
findMax IntMap a
t
| Just (Key, a)
r <- IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
lookupMax IntMap a
t = (Key, a)
r
| Bool
otherwise = [Char] -> (Key, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"findMax: empty map has no maximal element"
deleteMin :: IntMap a -> IntMap a
deleteMin :: IntMap a -> IntMap a
deleteMin = 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
forall a. IntMap a
Nil (a, IntMap a) -> IntMap a
forall a b. (a, b) -> b
snd (Maybe (a, IntMap a) -> IntMap a)
-> (IntMap a -> Maybe (a, IntMap a)) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe (a, IntMap a)
forall a. IntMap a -> Maybe (a, IntMap a)
minView
deleteMax :: IntMap a -> IntMap a
deleteMax :: IntMap a -> IntMap a
deleteMax = 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
forall a. IntMap a
Nil (a, IntMap a) -> IntMap a
forall a b. (a, b) -> b
snd (Maybe (a, IntMap a) -> IntMap a)
-> (IntMap a -> Maybe (a, IntMap a)) -> IntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe (a, IntMap a)
forall a. IntMap a -> Maybe (a, IntMap a)
maxView
isProperSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool
isProperSubmapOf :: IntMap a -> IntMap a -> Bool
isProperSubmapOf IntMap a
m1 IntMap a
m2
= (a -> a -> Bool) -> IntMap a -> IntMap a -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isProperSubmapOfBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) IntMap a
m1 IntMap a
m2
isProperSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isProperSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isProperSubmapOfBy a -> b -> Bool
predicate IntMap a
t1 IntMap b
t2
= case (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
submapCmp a -> b -> Bool
predicate IntMap a
t1 IntMap b
t2 of
Ordering
LT -> Bool
True
Ordering
_ -> Bool
False
submapCmp :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
submapCmp :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
submapCmp a -> b -> Bool
predicate t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) (Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
| Key -> Key -> Bool
shorter Key
m1 Key
m2 = Ordering
GT
| Key -> Key -> Bool
shorter Key
m2 Key
m1 = Ordering
submapCmpLt
| Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2 = Ordering
submapCmpEq
| Bool
otherwise = Ordering
GT
where
submapCmpLt :: Ordering
submapCmpLt | Key -> Key -> Key -> Bool
nomatch Key
p1 Key
p2 Key
m2 = Ordering
GT
| Key -> Key -> Bool
zero Key
p1 Key
m2 = (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
submapCmp a -> b -> Bool
predicate IntMap a
t1 IntMap b
l2
| Bool
otherwise = (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
submapCmp a -> b -> Bool
predicate IntMap a
t1 IntMap b
r2
submapCmpEq :: Ordering
submapCmpEq = case ((a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
submapCmp a -> b -> Bool
predicate IntMap a
l1 IntMap b
l2, (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Ordering
submapCmp a -> b -> Bool
predicate IntMap a
r1 IntMap b
r2) of
(Ordering
GT,Ordering
_ ) -> Ordering
GT
(Ordering
_ ,Ordering
GT) -> Ordering
GT
(Ordering
EQ,Ordering
EQ) -> Ordering
EQ
(Ordering, Ordering)
_ -> Ordering
LT
submapCmp a -> b -> Bool
_ (Bin Key
_ Key
_ IntMap a
_ IntMap a
_) IntMap b
_ = Ordering
GT
submapCmp a -> b -> Bool
predicate (Tip Key
kx a
x) (Tip Key
ky b
y)
| (Key
kx Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky) Bool -> Bool -> Bool
&& a -> b -> Bool
predicate a
x b
y = Ordering
EQ
| Bool
otherwise = Ordering
GT
submapCmp a -> b -> Bool
predicate (Tip Key
k a
x) IntMap b
t
= case Key -> IntMap b -> Maybe b
forall a. Key -> IntMap a -> Maybe a
lookup Key
k IntMap b
t of
Just b
y | a -> b -> Bool
predicate a
x b
y -> Ordering
LT
Maybe b
_ -> Ordering
GT
submapCmp a -> b -> Bool
_ IntMap a
Nil IntMap b
Nil = Ordering
EQ
submapCmp a -> b -> Bool
_ IntMap a
Nil IntMap b
_ = Ordering
LT
isSubmapOf :: Eq a => IntMap a -> IntMap a -> Bool
isSubmapOf :: IntMap a -> IntMap a -> Bool
isSubmapOf IntMap a
m1 IntMap a
m2
= (a -> a -> Bool) -> IntMap a -> IntMap a -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isSubmapOfBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
(==) IntMap a
m1 IntMap a
m2
isSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isSubmapOfBy :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isSubmapOfBy a -> b -> Bool
predicate t1 :: IntMap a
t1@(Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) (Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
| Key -> Key -> Bool
shorter Key
m1 Key
m2 = Bool
False
| Key -> Key -> Bool
shorter Key
m2 Key
m1 = Key -> Key -> Key -> Bool
match Key
p1 Key
p2 Key
m2 Bool -> Bool -> Bool
&&
if Key -> Key -> Bool
zero Key
p1 Key
m2
then (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isSubmapOfBy a -> b -> Bool
predicate IntMap a
t1 IntMap b
l2
else (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isSubmapOfBy a -> b -> Bool
predicate IntMap a
t1 IntMap b
r2
| Bool
otherwise = (Key
p1Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
==Key
p2) Bool -> Bool -> Bool
&& (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isSubmapOfBy a -> b -> Bool
predicate IntMap a
l1 IntMap b
l2 Bool -> Bool -> Bool
&& (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
isSubmapOfBy a -> b -> Bool
predicate IntMap a
r1 IntMap b
r2
isSubmapOfBy a -> b -> Bool
_ (Bin Key
_ Key
_ IntMap a
_ IntMap a
_) IntMap b
_ = Bool
False
isSubmapOfBy a -> b -> Bool
predicate (Tip Key
k a
x) IntMap b
t = case Key -> IntMap b -> Maybe b
forall a. Key -> IntMap a -> Maybe a
lookup Key
k IntMap b
t of
Just b
y -> a -> b -> Bool
predicate a
x b
y
Maybe b
Nothing -> Bool
False
isSubmapOfBy a -> b -> Bool
_ IntMap a
Nil IntMap b
_ = Bool
True
map :: (a -> b) -> IntMap a -> IntMap b
map :: (a -> b) -> IntMap a -> IntMap b
map a -> b
f = IntMap a -> IntMap b
go
where
go :: IntMap a -> IntMap b
go (Bin Key
p Key
m IntMap a
l IntMap a
r) = Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m (IntMap a -> IntMap b
go IntMap a
l) (IntMap a -> IntMap b
go IntMap a
r)
go (Tip Key
k a
x) = Key -> b -> IntMap b
forall a. Key -> a -> IntMap a
Tip Key
k (a -> b
f a
x)
go IntMap a
Nil = IntMap b
forall a. IntMap a
Nil
#ifdef __GLASGOW_HASKELL__
{-# NOINLINE [1] map #-}
{-# RULES
"map/map" forall f g xs . map f (map g xs) = map (f . g) xs
#-}
#endif
#if __GLASGOW_HASKELL__ >= 709
{-# RULES
"map/coerce" map coerce = coerce
#-}
#endif
mapWithKey :: (Key -> a -> b) -> IntMap a -> IntMap b
mapWithKey :: (Key -> a -> b) -> IntMap a -> IntMap b
mapWithKey Key -> a -> b
f IntMap a
t
= case IntMap a
t of
Bin Key
p Key
m IntMap a
l IntMap a
r -> Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m ((Key -> a -> b) -> IntMap a -> IntMap b
forall a b. (Key -> a -> b) -> IntMap a -> IntMap b
mapWithKey Key -> a -> b
f IntMap a
l) ((Key -> a -> b) -> IntMap a -> IntMap b
forall a b. (Key -> a -> b) -> IntMap a -> IntMap b
mapWithKey Key -> a -> b
f IntMap a
r)
Tip Key
k a
x -> Key -> b -> IntMap b
forall a. Key -> a -> IntMap a
Tip Key
k (Key -> a -> b
f Key
k a
x)
IntMap a
Nil -> IntMap b
forall a. IntMap a
Nil
#ifdef __GLASGOW_HASKELL__
{-# 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
#-}
#endif
traverseWithKey :: Applicative t => (Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseWithKey :: (Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseWithKey Key -> a -> t b
f = IntMap a -> t (IntMap b)
go
where
go :: IntMap a -> t (IntMap b)
go IntMap a
Nil = IntMap b -> t (IntMap b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure IntMap b
forall a. IntMap a
Nil
go (Tip Key
k a
v) = Key -> b -> IntMap b
forall a. Key -> a -> IntMap a
Tip Key
k (b -> IntMap b) -> t b -> t (IntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> t b
f Key
k a
v
go (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = (IntMap b -> IntMap b -> IntMap b)
-> t (IntMap b) -> t (IntMap b) -> t (IntMap b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((IntMap b -> IntMap b -> IntMap b)
-> IntMap b -> IntMap b -> IntMap b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m)) (IntMap a -> t (IntMap b)
go IntMap a
r) (IntMap a -> t (IntMap b)
go IntMap a
l)
| Bool
otherwise = (IntMap b -> IntMap b -> IntMap b)
-> t (IntMap b) -> t (IntMap b) -> t (IntMap b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 (Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m) (IntMap a -> t (IntMap b)
go IntMap a
l) (IntMap a -> t (IntMap b)
go IntMap a
r)
{-# INLINE traverseWithKey #-}
mapAccum :: (a -> b -> (a,c)) -> a -> IntMap b -> (a,IntMap c)
mapAccum :: (a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
mapAccum a -> b -> (a, c)
f = (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)
mapAccumWithKey (\a
a' Key
_ b
x -> a -> b -> (a, c)
f a
a' b
x)
mapAccumWithKey :: (a -> Key -> b -> (a,c)) -> a -> IntMap b -> (a,IntMap c)
mapAccumWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
mapAccumWithKey a -> Key -> b -> (a, c)
f a
a IntMap b
t
= (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)
mapAccumL a -> Key -> b -> (a, c)
f a
a IntMap b
t
mapAccumL :: (a -> Key -> b -> (a,c)) -> a -> IntMap b -> (a,IntMap c)
mapAccumL :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
mapAccumL a -> Key -> b -> (a, c)
f a
a IntMap b
t
= case IntMap b
t of
Bin Key
p Key
m IntMap b
l IntMap b
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 ->
let (a
a1,IntMap c
r') = (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)
mapAccumL a -> Key -> b -> (a, c)
f a
a IntMap b
r
(a
a2,IntMap c
l') = (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)
mapAccumL a -> Key -> b -> (a, c)
f a
a1 IntMap b
l
in (a
a2,Key -> Key -> IntMap c -> IntMap c -> IntMap c
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap c
l' IntMap c
r')
| Bool
otherwise ->
let (a
a1,IntMap c
l') = (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)
mapAccumL a -> Key -> b -> (a, c)
f a
a IntMap b
l
(a
a2,IntMap c
r') = (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)
mapAccumL a -> Key -> b -> (a, c)
f a
a1 IntMap b
r
in (a
a2,Key -> Key -> IntMap c -> IntMap c -> IntMap c
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap c
l' IntMap c
r')
Tip Key
k b
x -> let (a
a',c
x') = a -> Key -> b -> (a, c)
f a
a Key
k b
x in (a
a',Key -> c -> IntMap c
forall a. Key -> a -> IntMap a
Tip Key
k c
x')
IntMap b
Nil -> (a
a,IntMap c
forall a. IntMap a
Nil)
mapAccumRWithKey :: (a -> Key -> b -> (a,c)) -> a -> IntMap b -> (a,IntMap c)
mapAccumRWithKey :: (a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
mapAccumRWithKey a -> Key -> b -> (a, c)
f a
a IntMap b
t
= case IntMap b
t of
Bin Key
p Key
m IntMap b
l IntMap b
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 ->
let (a
a1,IntMap c
l') = (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)
mapAccumRWithKey a -> Key -> b -> (a, c)
f a
a IntMap b
l
(a
a2,IntMap c
r') = (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)
mapAccumRWithKey a -> Key -> b -> (a, c)
f a
a1 IntMap b
r
in (a
a2,Key -> Key -> IntMap c -> IntMap c -> IntMap c
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap c
l' IntMap c
r')
| Bool
otherwise ->
let (a
a1,IntMap c
r') = (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)
mapAccumRWithKey a -> Key -> b -> (a, c)
f a
a IntMap b
r
(a
a2,IntMap c
l') = (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)
mapAccumRWithKey a -> Key -> b -> (a, c)
f a
a1 IntMap b
l
in (a
a2,Key -> Key -> IntMap c -> IntMap c -> IntMap c
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap c
l' IntMap c
r')
Tip Key
k b
x -> let (a
a',c
x') = a -> Key -> b -> (a, c)
f a
a Key
k b
x in (a
a',Key -> c -> IntMap c
forall a. Key -> a -> IntMap a
Tip Key
k c
x')
IntMap b
Nil -> (a
a,IntMap c
forall a. IntMap a
Nil)
mapKeys :: (Key->Key) -> IntMap a -> IntMap a
mapKeys :: (Key -> Key) -> IntMap a -> IntMap a
mapKeys Key -> Key
f = [(Key, a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
fromList ([(Key, a)] -> IntMap a)
-> (IntMap a -> [(Key, a)]) -> IntMap a -> IntMap 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
foldrWithKey (\Key
k a
x [(Key, a)]
xs -> (Key -> Key
f Key
k, a
x) (Key, a) -> [(Key, a)] -> [(Key, a)]
forall a. a -> [a] -> [a]
: [(Key, a)]
xs) []
mapKeysWith :: (a -> a -> a) -> (Key->Key) -> IntMap a -> IntMap a
mapKeysWith :: (a -> a -> a) -> (Key -> Key) -> IntMap a -> IntMap a
mapKeysWith a -> a -> a
c Key -> Key
f
= (a -> a -> a) -> [(Key, a)] -> IntMap a
forall a. (a -> a -> a) -> [(Key, a)] -> IntMap a
fromListWith a -> a -> a
c ([(Key, a)] -> IntMap a)
-> (IntMap a -> [(Key, a)]) -> IntMap a -> IntMap 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
foldrWithKey (\Key
k a
x [(Key, a)]
xs -> (Key -> Key
f Key
k, a
x) (Key, a) -> [(Key, a)] -> [(Key, a)]
forall a. a -> [a] -> [a]
: [(Key, a)]
xs) []
mapKeysMonotonic :: (Key->Key) -> IntMap a -> IntMap a
mapKeysMonotonic :: (Key -> Key) -> IntMap a -> IntMap a
mapKeysMonotonic Key -> Key
f
= [(Key, a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
fromDistinctAscList ([(Key, a)] -> IntMap a)
-> (IntMap a -> [(Key, a)]) -> IntMap a -> IntMap 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
foldrWithKey (\Key
k a
x [(Key, a)]
xs -> (Key -> Key
f Key
k, a
x) (Key, a) -> [(Key, a)] -> [(Key, a)]
forall a. a -> [a] -> [a]
: [(Key, a)]
xs) []
filter :: (a -> Bool) -> IntMap a -> IntMap a
filter :: (a -> Bool) -> IntMap a -> IntMap a
filter a -> Bool
p IntMap a
m
= (Key -> a -> Bool) -> IntMap a -> IntMap a
forall a. (Key -> a -> Bool) -> IntMap a -> IntMap a
filterWithKey (\Key
_ a
x -> a -> Bool
p a
x) IntMap a
m
filterWithKey :: (Key -> a -> Bool) -> IntMap a -> IntMap a
filterWithKey :: (Key -> a -> Bool) -> IntMap a -> IntMap a
filterWithKey Key -> a -> Bool
predicate = IntMap a -> IntMap a
go
where
go :: IntMap a -> IntMap a
go IntMap a
Nil = IntMap a
forall a. IntMap a
Nil
go t :: IntMap a
t@(Tip Key
k a
x) = if Key -> a -> Bool
predicate Key
k a
x then IntMap a
t else IntMap a
forall a. IntMap a
Nil
go (Bin Key
p Key
m IntMap a
l IntMap a
r) = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m (IntMap a -> IntMap a
go IntMap a
l) (IntMap a -> IntMap a
go IntMap a
r)
partition :: (a -> Bool) -> IntMap a -> (IntMap a,IntMap a)
partition :: (a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
partition a -> Bool
p IntMap a
m
= (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
forall a. (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
partitionWithKey (\Key
_ a
x -> a -> Bool
p a
x) IntMap a
m
partitionWithKey :: (Key -> a -> Bool) -> IntMap a -> (IntMap a,IntMap a)
partitionWithKey :: (Key -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
partitionWithKey Key -> a -> Bool
predicate0 IntMap a
t0 = StrictPair (IntMap a) (IntMap a) -> (IntMap a, IntMap a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (IntMap a) (IntMap a) -> (IntMap a, IntMap a))
-> StrictPair (IntMap a) (IntMap a) -> (IntMap a, IntMap a)
forall a b. (a -> b) -> a -> b
$ (Key -> a -> Bool) -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a.
(Key -> a -> Bool) -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key -> a -> Bool
predicate0 IntMap a
t0
where
go :: (Key -> a -> Bool) -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key -> a -> Bool
predicate IntMap a
t =
case IntMap a
t of
Bin Key
p Key
m IntMap a
l IntMap a
r ->
let (IntMap a
l1 :*: IntMap a
l2) = (Key -> a -> Bool) -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key -> a -> Bool
predicate IntMap a
l
(IntMap a
r1 :*: IntMap a
r2) = (Key -> a -> Bool) -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key -> a -> Bool
predicate IntMap a
r
in Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m IntMap a
l1 IntMap a
r1 IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m IntMap a
l2 IntMap a
r2
Tip Key
k a
x
| Key -> a -> Bool
predicate Key
k a
x -> (IntMap a
t IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
| Bool
otherwise -> (IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
t)
IntMap a
Nil -> (IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b
mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b
mapMaybe a -> Maybe b
f = (Key -> a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (Key -> a -> Maybe b) -> IntMap a -> IntMap b
mapMaybeWithKey (\Key
_ a
x -> a -> Maybe b
f a
x)
mapMaybeWithKey :: (Key -> a -> Maybe b) -> IntMap a -> IntMap b
mapMaybeWithKey :: (Key -> a -> Maybe b) -> IntMap a -> IntMap b
mapMaybeWithKey Key -> a -> Maybe b
f (Bin Key
p Key
m IntMap a
l IntMap a
r)
= Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m ((Key -> a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (Key -> a -> Maybe b) -> IntMap a -> IntMap b
mapMaybeWithKey Key -> a -> Maybe b
f IntMap a
l) ((Key -> a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (Key -> a -> Maybe b) -> IntMap a -> IntMap b
mapMaybeWithKey Key -> a -> Maybe b
f IntMap a
r)
mapMaybeWithKey Key -> a -> Maybe b
f (Tip Key
k a
x) = case Key -> a -> Maybe b
f Key
k a
x of
Just b
y -> Key -> b -> IntMap b
forall a. Key -> a -> IntMap a
Tip Key
k b
y
Maybe b
Nothing -> IntMap b
forall a. IntMap a
Nil
mapMaybeWithKey Key -> a -> Maybe b
_ IntMap a
Nil = IntMap b
forall a. IntMap a
Nil
mapEither :: (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
mapEither :: (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
mapEither a -> Either b c
f IntMap a
m
= (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)
mapEitherWithKey (\Key
_ a
x -> a -> Either b c
f a
x) IntMap a
m
mapEitherWithKey :: (Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
mapEitherWithKey :: (Key -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
mapEitherWithKey Key -> a -> Either b c
f0 IntMap a
t0 = StrictPair (IntMap b) (IntMap c) -> (IntMap b, IntMap c)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (IntMap b) (IntMap c) -> (IntMap b, IntMap c))
-> StrictPair (IntMap b) (IntMap c) -> (IntMap b, IntMap c)
forall a b. (a -> b) -> a -> b
$ (Key -> a -> Either b c)
-> IntMap a -> StrictPair (IntMap b) (IntMap c)
forall t a a.
(Key -> t -> Either a a)
-> IntMap t -> StrictPair (IntMap a) (IntMap a)
go Key -> a -> Either b c
f0 IntMap a
t0
where
go :: (Key -> t -> Either a a)
-> IntMap t -> StrictPair (IntMap a) (IntMap a)
go Key -> t -> Either a a
f (Bin Key
p Key
m IntMap t
l IntMap t
r) =
Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m IntMap a
l1 IntMap a
r1 IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
p Key
m IntMap a
l2 IntMap a
r2
where
(IntMap a
l1 :*: IntMap a
l2) = (Key -> t -> Either a a)
-> IntMap t -> StrictPair (IntMap a) (IntMap a)
go Key -> t -> Either a a
f IntMap t
l
(IntMap a
r1 :*: IntMap a
r2) = (Key -> t -> Either a a)
-> IntMap t -> StrictPair (IntMap a) (IntMap a)
go Key -> t -> Either a a
f IntMap t
r
go Key -> t -> Either a a
f (Tip Key
k t
x) = case Key -> t -> Either a a
f Key
k t
x of
Left a
y -> (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
y IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
Right a
z -> (IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
z)
go Key -> t -> Either a a
_ IntMap t
Nil = (IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
split :: Key -> IntMap a -> (IntMap a, IntMap a)
split :: Key -> IntMap a -> (IntMap a, IntMap a)
split Key
k IntMap a
t =
case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 ->
if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
>= Key
0
then
case Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a. Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key
k IntMap a
l of
(IntMap a
lt :*: IntMap a
gt) ->
let !lt' :: IntMap a
lt' = IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union IntMap a
r IntMap a
lt
in (IntMap a
lt', IntMap a
gt)
else
case Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a. Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key
k IntMap a
r of
(IntMap a
lt :*: IntMap a
gt) ->
let !gt' :: IntMap a
gt' = IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union IntMap a
gt IntMap a
l
in (IntMap a
lt, IntMap a
gt')
IntMap a
_ -> case Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a. Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key
k IntMap a
t of
(IntMap a
lt :*: IntMap a
gt) -> (IntMap a
lt, IntMap a
gt)
where
go :: Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key
k' t' :: IntMap a
t'@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k' Key
p Key
m = if Key
k' Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
p then IntMap a
t' IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil else IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
t'
| Key -> Key -> Bool
zero Key
k' Key
m = case Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key
k' IntMap a
l of (IntMap a
lt :*: IntMap a
gt) -> IntMap a
lt IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union IntMap a
gt IntMap a
r
| Bool
otherwise = case Key -> IntMap a -> StrictPair (IntMap a) (IntMap a)
go Key
k' IntMap a
r of (IntMap a
lt :*: IntMap a
gt) -> IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union IntMap a
l IntMap a
lt IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
gt
go Key
k' t' :: IntMap a
t'@(Tip Key
ky a
_)
| Key
k' Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
ky = (IntMap a
t' IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
| Key
k' Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
ky = (IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
t')
| Bool
otherwise = (IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
go Key
_ IntMap a
Nil = (IntMap a
forall a. IntMap a
Nil IntMap a -> IntMap a -> StrictPair (IntMap a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
data SplitLookup a = SplitLookup !(IntMap a) !(Maybe a) !(IntMap a)
mapLT :: (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapLT :: (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapLT IntMap a -> IntMap a
f (SplitLookup IntMap a
lt Maybe a
fnd IntMap a
gt) = IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup (IntMap a -> IntMap a
f IntMap a
lt) Maybe a
fnd IntMap a
gt
{-# INLINE mapLT #-}
mapGT :: (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapGT :: (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapGT IntMap a -> IntMap a
f (SplitLookup IntMap a
lt Maybe a
fnd IntMap a
gt) = IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup IntMap a
lt Maybe a
fnd (IntMap a -> IntMap a
f IntMap a
gt)
{-# INLINE mapGT #-}
splitLookup :: Key -> IntMap a -> (IntMap a, Maybe a, IntMap a)
splitLookup :: Key -> IntMap a -> (IntMap a, Maybe a, IntMap a)
splitLookup Key
k IntMap a
t =
case
case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 ->
if Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
>= Key
0
then (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
forall a. (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapLT (IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union IntMap a
r) (Key -> IntMap a -> SplitLookup a
forall a. Key -> IntMap a -> SplitLookup a
go Key
k IntMap a
l)
else (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
forall a. (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapGT (IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
`union` IntMap a
l) (Key -> IntMap a -> SplitLookup a
forall a. Key -> IntMap a -> SplitLookup a
go Key
k IntMap a
r)
IntMap a
_ -> Key -> IntMap a -> SplitLookup a
forall a. Key -> IntMap a -> SplitLookup a
go Key
k IntMap a
t
of SplitLookup IntMap a
lt Maybe a
fnd IntMap a
gt -> (IntMap a
lt, Maybe a
fnd, IntMap a
gt)
where
go :: Key -> IntMap a -> SplitLookup a
go Key
k' t' :: IntMap a
t'@(Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key -> Key -> Key -> Bool
nomatch Key
k' Key
p Key
m =
if Key
k' Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
p
then IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup IntMap a
t' Maybe a
forall a. Maybe a
Nothing IntMap a
forall a. IntMap a
Nil
else IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup IntMap a
forall a. IntMap a
Nil Maybe a
forall a. Maybe a
Nothing IntMap a
t'
| Key -> Key -> Bool
zero Key
k' Key
m = (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
forall a. (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapGT (IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
`union` IntMap a
r) (Key -> IntMap a -> SplitLookup a
go Key
k' IntMap a
l)
| Bool
otherwise = (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
forall a. (IntMap a -> IntMap a) -> SplitLookup a -> SplitLookup a
mapLT (IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
union IntMap a
l) (Key -> IntMap a -> SplitLookup a
go Key
k' IntMap a
r)
go Key
k' t' :: IntMap a
t'@(Tip Key
ky a
y)
| Key
k' Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
ky = IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup IntMap a
t' Maybe a
forall a. Maybe a
Nothing IntMap a
forall a. IntMap a
Nil
| Key
k' Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
ky = IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup IntMap a
forall a. IntMap a
Nil Maybe a
forall a. Maybe a
Nothing IntMap a
t'
| Bool
otherwise = IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup IntMap a
forall a. IntMap a
Nil (a -> Maybe a
forall a. a -> Maybe a
Just a
y) IntMap a
forall a. IntMap a
Nil
go Key
_ IntMap a
Nil = IntMap a -> Maybe a -> IntMap a -> SplitLookup a
forall a. IntMap a -> Maybe a -> IntMap a -> SplitLookup a
SplitLookup IntMap a
forall a. IntMap a
Nil Maybe a
forall a. Maybe a
Nothing IntMap a
forall a. IntMap a
Nil
foldr :: (a -> b -> b) -> b -> IntMap a -> b
foldr :: (a -> b -> b) -> b -> IntMap a -> b
foldr a -> b -> b
f b
z = \IntMap a
t ->
case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
l) IntMap a
r
| Bool
otherwise -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
r) IntMap a
l
IntMap a
_ -> b -> IntMap a -> b
go b
z IntMap a
t
where
go :: b -> IntMap a -> b
go b
z' IntMap a
Nil = b
z'
go b
z' (Tip Key
_ a
x) = a -> b -> b
f a
x b
z'
go b
z' (Bin Key
_ Key
_ IntMap a
l IntMap a
r) = b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z' IntMap a
r) IntMap a
l
{-# INLINE foldr #-}
foldr' :: (a -> b -> b) -> b -> IntMap a -> b
foldr' :: (a -> b -> b) -> b -> IntMap a -> b
foldr' a -> b -> b
f b
z = \IntMap a
t ->
case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
l) IntMap a
r
| Bool
otherwise -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
r) IntMap a
l
IntMap a
_ -> b -> IntMap a -> b
go b
z IntMap a
t
where
go :: b -> IntMap a -> b
go !b
z' IntMap a
Nil = b
z'
go b
z' (Tip Key
_ a
x) = a -> b -> b
f a
x b
z'
go b
z' (Bin Key
_ Key
_ IntMap a
l IntMap a
r) = b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z' IntMap a
r) IntMap a
l
{-# INLINE foldr' #-}
foldl :: (a -> b -> a) -> a -> IntMap b -> a
foldl :: (a -> b -> a) -> a -> IntMap b -> a
foldl a -> b -> a
f a
z = \IntMap b
t ->
case IntMap b
t of
Bin Key
_ Key
m IntMap b
l IntMap b
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
r) IntMap b
l
| Bool
otherwise -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
l) IntMap b
r
IntMap b
_ -> a -> IntMap b -> a
go a
z IntMap b
t
where
go :: a -> IntMap b -> a
go a
z' IntMap b
Nil = a
z'
go a
z' (Tip Key
_ b
x) = a -> b -> a
f a
z' b
x
go a
z' (Bin Key
_ Key
_ IntMap b
l IntMap b
r) = a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z' IntMap b
l) IntMap b
r
{-# INLINE foldl #-}
foldl' :: (a -> b -> a) -> a -> IntMap b -> a
foldl' :: (a -> b -> a) -> a -> IntMap b -> a
foldl' a -> b -> a
f a
z = \IntMap b
t ->
case IntMap b
t of
Bin Key
_ Key
m IntMap b
l IntMap b
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
r) IntMap b
l
| Bool
otherwise -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
l) IntMap b
r
IntMap b
_ -> a -> IntMap b -> a
go a
z IntMap b
t
where
go :: a -> IntMap b -> a
go !a
z' IntMap b
Nil = a
z'
go a
z' (Tip Key
_ b
x) = a -> b -> a
f a
z' b
x
go a
z' (Bin Key
_ Key
_ IntMap b
l IntMap b
r) = a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z' IntMap b
l) IntMap b
r
{-# INLINE foldl' #-}
foldrWithKey :: (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey :: (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey Key -> a -> b -> b
f b
z = \IntMap a
t ->
case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
l) IntMap a
r
| Bool
otherwise -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
r) IntMap a
l
IntMap a
_ -> b -> IntMap a -> b
go b
z IntMap a
t
where
go :: b -> IntMap a -> b
go b
z' IntMap a
Nil = b
z'
go b
z' (Tip Key
kx a
x) = Key -> a -> b -> b
f Key
kx a
x b
z'
go b
z' (Bin Key
_ Key
_ IntMap a
l IntMap a
r) = b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z' IntMap a
r) IntMap a
l
{-# INLINE foldrWithKey #-}
foldrWithKey' :: (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey' :: (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey' Key -> a -> b -> b
f b
z = \IntMap a
t ->
case IntMap a
t of
Bin Key
_ Key
m IntMap a
l IntMap a
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
l) IntMap a
r
| Bool
otherwise -> b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z IntMap a
r) IntMap a
l
IntMap a
_ -> b -> IntMap a -> b
go b
z IntMap a
t
where
go :: b -> IntMap a -> b
go !b
z' IntMap a
Nil = b
z'
go b
z' (Tip Key
kx a
x) = Key -> a -> b -> b
f Key
kx a
x b
z'
go b
z' (Bin Key
_ Key
_ IntMap a
l IntMap a
r) = b -> IntMap a -> b
go (b -> IntMap a -> b
go b
z' IntMap a
r) IntMap a
l
{-# INLINE foldrWithKey' #-}
foldlWithKey :: (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlWithKey :: (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlWithKey a -> Key -> b -> a
f a
z = \IntMap b
t ->
case IntMap b
t of
Bin Key
_ Key
m IntMap b
l IntMap b
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
r) IntMap b
l
| Bool
otherwise -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
l) IntMap b
r
IntMap b
_ -> a -> IntMap b -> a
go a
z IntMap b
t
where
go :: a -> IntMap b -> a
go a
z' IntMap b
Nil = a
z'
go a
z' (Tip Key
kx b
x) = a -> Key -> b -> a
f a
z' Key
kx b
x
go a
z' (Bin Key
_ Key
_ IntMap b
l IntMap b
r) = a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z' IntMap b
l) IntMap b
r
{-# INLINE foldlWithKey #-}
foldlWithKey' :: (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlWithKey' :: (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlWithKey' a -> Key -> b -> a
f a
z = \IntMap b
t ->
case IntMap b
t of
Bin Key
_ Key
m IntMap b
l IntMap b
r
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
r) IntMap b
l
| Bool
otherwise -> a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z IntMap b
l) IntMap b
r
IntMap b
_ -> a -> IntMap b -> a
go a
z IntMap b
t
where
go :: a -> IntMap b -> a
go !a
z' IntMap b
Nil = a
z'
go a
z' (Tip Key
kx b
x) = a -> Key -> b -> a
f a
z' Key
kx b
x
go a
z' (Bin Key
_ Key
_ IntMap b
l IntMap b
r) = a -> IntMap b -> a
go (a -> IntMap b -> a
go a
z' IntMap b
l) IntMap b
r
{-# INLINE foldlWithKey' #-}
foldMapWithKey :: Monoid m => (Key -> a -> m) -> IntMap a -> m
foldMapWithKey :: (Key -> a -> m) -> IntMap a -> m
foldMapWithKey Key -> a -> m
f = IntMap a -> m
go
where
go :: IntMap a -> m
go IntMap a
Nil = m
forall a. Monoid a => a
mempty
go (Tip Key
kx a
x) = Key -> a -> m
f Key
kx a
x
go (Bin Key
_ Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 = IntMap a -> m
go IntMap a
r m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` IntMap a -> m
go IntMap a
l
| Bool
otherwise = IntMap a -> m
go IntMap a
l m -> m -> m
forall a. Monoid a => a -> a -> a
`mappend` IntMap a -> m
go IntMap a
r
{-# INLINE foldMapWithKey #-}
elems :: IntMap a -> [a]
elems :: IntMap a -> [a]
elems = (a -> [a] -> [a]) -> [a] -> IntMap a -> [a]
forall a b. (a -> b -> b) -> b -> IntMap a -> b
foldr (:) []
keys :: IntMap a -> [Key]
keys :: IntMap a -> [Key]
keys = (Key -> a -> [Key] -> [Key]) -> [Key] -> IntMap a -> [Key]
forall a b. (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey (\Key
k a
_ [Key]
ks -> Key
k Key -> [Key] -> [Key]
forall a. a -> [a] -> [a]
: [Key]
ks) []
assocs :: IntMap a -> [(Key,a)]
assocs :: IntMap a -> [(Key, a)]
assocs = IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toAscList
keysSet :: IntMap a -> IntSet.IntSet
keysSet :: IntMap a -> IntSet
keysSet IntMap a
Nil = IntSet
IntSet.Nil
keysSet (Tip Key
kx a
_) = Key -> IntSet
IntSet.singleton Key
kx
keysSet (Bin Key
p Key
m IntMap a
l IntMap a
r)
| Key
m Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.suffixBitMask Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
0 = Key -> Key -> IntSet -> IntSet -> IntSet
IntSet.Bin Key
p Key
m (IntMap a -> IntSet
forall a. IntMap a -> IntSet
keysSet IntMap a
l) (IntMap a -> IntSet
forall a. IntMap a -> IntSet
keysSet IntMap a
r)
| Bool
otherwise = Key -> Nat -> IntSet
IntSet.Tip (Key
p Key -> Key -> Key
forall a. Bits a => a -> a -> a
.&. Key
IntSet.prefixBitMask) (Nat -> IntMap a -> Nat
forall a. Nat -> IntMap a -> Nat
computeBm (Nat -> IntMap a -> Nat
forall a. Nat -> IntMap a -> Nat
computeBm Nat
0 IntMap a
l) IntMap a
r)
where computeBm :: Nat -> IntMap a -> Nat
computeBm !Nat
acc (Bin Key
_ Key
_ IntMap a
l' IntMap a
r') = Nat -> IntMap a -> Nat
computeBm (Nat -> IntMap a -> Nat
computeBm Nat
acc IntMap a
l') IntMap a
r'
computeBm Nat
acc (Tip Key
kx a
_) = Nat
acc Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.|. Key -> Nat
IntSet.bitmapOf Key
kx
computeBm Nat
_ IntMap a
Nil = [Char] -> Nat
forall a. HasCallStack => [Char] -> a
error [Char]
"Data.IntSet.keysSet: Nil"
fromSet :: (Key -> a) -> IntSet.IntSet -> IntMap a
fromSet :: (Key -> a) -> IntSet -> IntMap a
fromSet Key -> a
_ IntSet
IntSet.Nil = IntMap a
forall a. IntMap a
Nil
fromSet Key -> a
f (IntSet.Bin Key
p Key
m IntSet
l IntSet
r) = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m ((Key -> a) -> IntSet -> IntMap a
forall a. (Key -> a) -> IntSet -> IntMap a
fromSet Key -> a
f IntSet
l) ((Key -> a) -> IntSet -> IntMap a
forall a. (Key -> a) -> IntSet -> IntMap a
fromSet Key -> a
f IntSet
r)
fromSet Key -> a
f (IntSet.Tip Key
kx Nat
bm) = (Key -> a) -> Key -> Nat -> Key -> IntMap a
forall a. (Key -> a) -> Key -> Nat -> Key -> IntMap a
buildTree Key -> a
f Key
kx Nat
bm (Key
IntSet.suffixBitMask Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
1)
where
buildTree :: (Key -> a) -> Key -> Nat -> Key -> IntMap a
buildTree Key -> a
g !Key
prefix !Nat
bmask Key
bits = case Key
bits of
Key
0 -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
prefix (Key -> a
g Key
prefix)
Key
_ -> case Nat -> Key
intFromNat ((Key -> Nat
natFromInt Key
bits) Nat -> Key -> Nat
`shiftRL` Key
1) of
Key
bits2
| Nat
bmask Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. ((Nat
1 Nat -> Key -> Nat
`shiftLL` Key
bits2) Nat -> Nat -> Nat
forall a. Num a => a -> a -> a
- Nat
1) Nat -> Nat -> Bool
forall a. Eq a => a -> a -> Bool
== Nat
0 ->
(Key -> a) -> Key -> Nat -> Key -> IntMap a
buildTree Key -> a
g (Key
prefix Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
bits2) (Nat
bmask Nat -> Key -> Nat
`shiftRL` Key
bits2) Key
bits2
| (Nat
bmask Nat -> Key -> Nat
`shiftRL` Key
bits2) Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. ((Nat
1 Nat -> Key -> Nat
`shiftLL` Key
bits2) Nat -> Nat -> Nat
forall a. Num a => a -> a -> a
- Nat
1) Nat -> Nat -> Bool
forall a. Eq a => a -> a -> Bool
== Nat
0 ->
(Key -> a) -> Key -> Nat -> Key -> IntMap a
buildTree Key -> a
g Key
prefix Nat
bmask Key
bits2
| Bool
otherwise ->
Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
prefix Key
bits2
((Key -> a) -> Key -> Nat -> Key -> IntMap a
buildTree Key -> a
g Key
prefix Nat
bmask Key
bits2)
((Key -> a) -> Key -> Nat -> Key -> IntMap a
buildTree Key -> a
g (Key
prefix Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
bits2) (Nat
bmask Nat -> Key -> Nat
`shiftRL` Key
bits2) Key
bits2)
#if __GLASGOW_HASKELL__ >= 708
instance GHCExts.IsList (IntMap a) where
type Item (IntMap a) = (Key,a)
fromList :: [Item (IntMap a)] -> IntMap a
fromList = [Item (IntMap a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
fromList
toList :: IntMap a -> [Item (IntMap a)]
toList = IntMap a -> [Item (IntMap a)]
forall a. IntMap a -> [(Key, a)]
toList
#endif
toList :: IntMap a -> [(Key,a)]
toList :: IntMap a -> [(Key, a)]
toList = IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toAscList
toAscList :: IntMap a -> [(Key,a)]
toAscList :: IntMap a -> [(Key, a)]
toAscList = (Key -> a -> [(Key, a)] -> [(Key, a)])
-> [(Key, a)] -> IntMap a -> [(Key, a)]
forall a b. (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey (\Key
k a
x [(Key, a)]
xs -> (Key
k,a
x)(Key, a) -> [(Key, a)] -> [(Key, a)]
forall a. a -> [a] -> [a]
:[(Key, a)]
xs) []
toDescList :: IntMap a -> [(Key,a)]
toDescList :: IntMap a -> [(Key, a)]
toDescList = ([(Key, a)] -> Key -> a -> [(Key, a)])
-> [(Key, a)] -> IntMap a -> [(Key, a)]
forall a b. (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlWithKey (\[(Key, a)]
xs Key
k a
x -> (Key
k,a
x)(Key, a) -> [(Key, a)] -> [(Key, a)]
forall a. a -> [a] -> [a]
:[(Key, a)]
xs) []
#if __GLASGOW_HASKELL__
foldrFB :: (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrFB :: (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrFB = (Key -> a -> b -> b) -> b -> IntMap a -> b
forall a b. (Key -> a -> b -> b) -> b -> IntMap a -> b
foldrWithKey
{-# INLINE[0] foldrFB #-}
foldlFB :: (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlFB :: (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlFB = (a -> Key -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> Key -> b -> a) -> a -> IntMap b -> a
foldlWithKey
{-# INLINE[0] foldlFB #-}
{-# INLINE assocs #-}
{-# INLINE toList #-}
{-# NOINLINE[0] elems #-}
{-# NOINLINE[0] keys #-}
{-# NOINLINE[0] toAscList #-}
{-# NOINLINE[0] toDescList #-}
{-# RULES "IntMap.elems" [~1] forall m . elems m = build (\c n -> foldrFB (\_ x xs -> c x xs) n m) #-}
{-# RULES "IntMap.elemsBack" [1] foldrFB (\_ x xs -> x : xs) [] = elems #-}
{-# RULES "IntMap.keys" [~1] forall m . keys m = build (\c n -> foldrFB (\k _ xs -> c k xs) n m) #-}
{-# RULES "IntMap.keysBack" [1] foldrFB (\k _ xs -> k : xs) [] = keys #-}
{-# RULES "IntMap.toAscList" [~1] forall m . toAscList m = build (\c n -> foldrFB (\k x xs -> c (k,x) xs) n m) #-}
{-# RULES "IntMap.toAscListBack" [1] foldrFB (\k x xs -> (k, x) : xs) [] = toAscList #-}
{-# RULES "IntMap.toDescList" [~1] forall m . toDescList m = build (\c n -> foldlFB (\xs k x -> c (k,x) xs) n m) #-}
{-# RULES "IntMap.toDescListBack" [1] foldlFB (\xs k x -> (k, x) : xs) [] = toDescList #-}
#endif
fromList :: [(Key,a)] -> IntMap a
fromList :: [(Key, a)] -> IntMap a
fromList [(Key, a)]
xs
= (IntMap a -> (Key, a) -> IntMap a)
-> IntMap a -> [(Key, a)] -> IntMap a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl' IntMap a -> (Key, a) -> IntMap a
forall a. IntMap a -> (Key, a) -> IntMap a
ins IntMap a
forall a. IntMap a
empty [(Key, a)]
xs
where
ins :: IntMap a -> (Key, a) -> IntMap a
ins IntMap a
t (Key
k,a
x) = Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insert Key
k a
x IntMap a
t
fromListWith :: (a -> a -> a) -> [(Key,a)] -> IntMap a
fromListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a
fromListWith a -> a -> a
f [(Key, a)]
xs
= (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
forall a. (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromListWithKey (\Key
_ a
x a
y -> a -> a -> a
f a
x a
y) [(Key, a)]
xs
fromListWithKey :: (Key -> a -> a -> a) -> [(Key,a)] -> IntMap a
fromListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromListWithKey Key -> a -> a -> a
f [(Key, a)]
xs
= (IntMap a -> (Key, a) -> IntMap a)
-> IntMap a -> [(Key, a)] -> IntMap a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Foldable.foldl' IntMap a -> (Key, a) -> IntMap a
ins IntMap a
forall a. IntMap a
empty [(Key, a)]
xs
where
ins :: IntMap a -> (Key, a) -> IntMap a
ins IntMap a
t (Key
k,a
x) = (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
forall a. (Key -> a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
insertWithKey Key -> a -> a -> a
f Key
k a
x IntMap a
t
fromAscList :: [(Key,a)] -> IntMap a
fromAscList :: [(Key, a)] -> IntMap a
fromAscList = Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
forall a.
Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromMonoListWithKey Distinct
Nondistinct (\Key
_ a
x a
_ -> a
x)
{-# NOINLINE fromAscList #-}
fromAscListWith :: (a -> a -> a) -> [(Key,a)] -> IntMap a
fromAscListWith :: (a -> a -> a) -> [(Key, a)] -> IntMap a
fromAscListWith a -> a -> a
f = Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
forall a.
Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromMonoListWithKey Distinct
Nondistinct (\Key
_ a
x a
y -> a -> a -> a
f a
x a
y)
{-# NOINLINE fromAscListWith #-}
fromAscListWithKey :: (Key -> a -> a -> a) -> [(Key,a)] -> IntMap a
fromAscListWithKey :: (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromAscListWithKey Key -> a -> a -> a
f = Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
forall a.
Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromMonoListWithKey Distinct
Nondistinct Key -> a -> a -> a
f
{-# NOINLINE fromAscListWithKey #-}
fromDistinctAscList :: [(Key,a)] -> IntMap a
fromDistinctAscList :: [(Key, a)] -> IntMap a
fromDistinctAscList = Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
forall a.
Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromMonoListWithKey Distinct
Distinct (\Key
_ a
x a
_ -> a
x)
{-# NOINLINE fromDistinctAscList #-}
fromMonoListWithKey :: Distinct -> (Key -> a -> a -> a) -> [(Key,a)] -> IntMap a
fromMonoListWithKey :: Distinct -> (Key -> a -> a -> a) -> [(Key, a)] -> IntMap a
fromMonoListWithKey Distinct
distinct Key -> a -> a -> a
f = [(Key, a)] -> IntMap a
go
where
go :: [(Key, a)] -> IntMap a
go [] = IntMap a
forall a. IntMap a
Nil
go ((Key
kx,a
vx) : [(Key, a)]
zs1) = Key -> a -> [(Key, a)] -> IntMap a
addAll' Key
kx a
vx [(Key, a)]
zs1
addAll' :: Key -> a -> [(Key, a)] -> IntMap a
addAll' !Key
kx a
vx []
= Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
kx a
vx
addAll' !Key
kx a
vx ((Key
ky,a
vy) : [(Key, a)]
zs)
| Distinct
Nondistinct <- Distinct
distinct, Key
kx Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky
= let v :: a
v = Key -> a -> a -> a
f Key
kx a
vy a
vx in Key -> a -> [(Key, a)] -> IntMap a
addAll' Key
ky a
v [(Key, a)]
zs
| Key
m <- Key -> Key -> Key
branchMask Key
kx Key
ky
, Inserted IntMap a
ty [(Key, a)]
zs' <- Key -> Key -> a -> [(Key, a)] -> Inserted a
addMany' Key
m Key
ky a
vy [(Key, a)]
zs
= Key -> IntMap a -> [(Key, a)] -> IntMap a
addAll Key
kx (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
linkWithMask Key
m Key
ky IntMap a
ty (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
kx a
vx)) [(Key, a)]
zs'
addAll :: Key -> IntMap a -> [(Key, a)] -> IntMap a
addAll !Key
_kx !IntMap a
tx []
= IntMap a
tx
addAll !Key
kx !IntMap a
tx ((Key
ky,a
vy) : [(Key, a)]
zs)
| Key
m <- Key -> Key -> Key
branchMask Key
kx Key
ky
, Inserted IntMap a
ty [(Key, a)]
zs' <- Key -> Key -> a -> [(Key, a)] -> Inserted a
addMany' Key
m Key
ky a
vy [(Key, a)]
zs
= Key -> IntMap a -> [(Key, a)] -> IntMap a
addAll Key
kx (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
linkWithMask Key
m Key
ky IntMap a
ty IntMap a
tx) [(Key, a)]
zs'
addMany' :: Key -> Key -> a -> [(Key, a)] -> Inserted a
addMany' !Key
_m !Key
kx a
vx []
= IntMap a -> [(Key, a)] -> Inserted a
forall a. IntMap a -> [(Key, a)] -> Inserted a
Inserted (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
kx a
vx) []
addMany' !Key
m !Key
kx a
vx zs0 :: [(Key, a)]
zs0@((Key
ky,a
vy) : [(Key, a)]
zs)
| Distinct
Nondistinct <- Distinct
distinct, Key
kx Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky
= let v :: a
v = Key -> a -> a -> a
f Key
kx a
vy a
vx in Key -> Key -> a -> [(Key, a)] -> Inserted a
addMany' Key
m Key
ky a
v [(Key, a)]
zs
| Key -> Key -> Key
mask Key
kx Key
m Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key -> Key -> Key
mask Key
ky Key
m
= IntMap a -> [(Key, a)] -> Inserted a
forall a. IntMap a -> [(Key, a)] -> Inserted a
Inserted (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
kx a
vx) [(Key, a)]
zs0
| Key
mxy <- Key -> Key -> Key
branchMask Key
kx Key
ky
, Inserted IntMap a
ty [(Key, a)]
zs' <- Key -> Key -> a -> [(Key, a)] -> Inserted a
addMany' Key
mxy Key
ky a
vy [(Key, a)]
zs
= Key -> Key -> IntMap a -> [(Key, a)] -> Inserted a
addMany Key
m Key
kx (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
linkWithMask Key
mxy Key
ky IntMap a
ty (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
kx a
vx)) [(Key, a)]
zs'
addMany :: Key -> Key -> IntMap a -> [(Key, a)] -> Inserted a
addMany !Key
_m !Key
_kx IntMap a
tx []
= IntMap a -> [(Key, a)] -> Inserted a
forall a. IntMap a -> [(Key, a)] -> Inserted a
Inserted IntMap a
tx []
addMany !Key
m !Key
kx IntMap a
tx zs0 :: [(Key, a)]
zs0@((Key
ky,a
vy) : [(Key, a)]
zs)
| Key -> Key -> Key
mask Key
kx Key
m Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key -> Key -> Key
mask Key
ky Key
m
= IntMap a -> [(Key, a)] -> Inserted a
forall a. IntMap a -> [(Key, a)] -> Inserted a
Inserted IntMap a
tx [(Key, a)]
zs0
| Key
mxy <- Key -> Key -> Key
branchMask Key
kx Key
ky
, Inserted IntMap a
ty [(Key, a)]
zs' <- Key -> Key -> a -> [(Key, a)] -> Inserted a
addMany' Key
mxy Key
ky a
vy [(Key, a)]
zs
= Key -> Key -> IntMap a -> [(Key, a)] -> Inserted a
addMany Key
m Key
kx (Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
linkWithMask Key
mxy Key
ky IntMap a
ty IntMap a
tx) [(Key, a)]
zs'
{-# INLINE fromMonoListWithKey #-}
data Inserted a = Inserted !(IntMap a) ![(Key,a)]
data Distinct = Distinct | Nondistinct
instance Eq a => Eq (IntMap a) where
IntMap a
t1 == :: IntMap a -> IntMap a -> Bool
== IntMap a
t2 = IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
equal IntMap a
t1 IntMap a
t2
IntMap a
t1 /= :: IntMap a -> IntMap a -> Bool
/= IntMap a
t2 = IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
nequal IntMap a
t1 IntMap a
t2
equal :: Eq a => IntMap a -> IntMap a -> Bool
equal :: IntMap a -> IntMap a -> Bool
equal (Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) (Bin Key
p2 Key
m2 IntMap a
l2 IntMap a
r2)
= (Key
m1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
m2) Bool -> Bool -> Bool
&& (Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2) Bool -> Bool -> Bool
&& (IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
equal IntMap a
l1 IntMap a
l2) Bool -> Bool -> Bool
&& (IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
equal IntMap a
r1 IntMap a
r2)
equal (Tip Key
kx a
x) (Tip Key
ky a
y)
= (Key
kx Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky) Bool -> Bool -> Bool
&& (a
xa -> a -> Bool
forall a. Eq a => a -> a -> Bool
==a
y)
equal IntMap a
Nil IntMap a
Nil = Bool
True
equal IntMap a
_ IntMap a
_ = Bool
False
nequal :: Eq a => IntMap a -> IntMap a -> Bool
nequal :: IntMap a -> IntMap a -> Bool
nequal (Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) (Bin Key
p2 Key
m2 IntMap a
l2 IntMap a
r2)
= (Key
m1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
m2) Bool -> Bool -> Bool
|| (Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
p2) Bool -> Bool -> Bool
|| (IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
nequal IntMap a
l1 IntMap a
l2) Bool -> Bool -> Bool
|| (IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
nequal IntMap a
r1 IntMap a
r2)
nequal (Tip Key
kx a
x) (Tip Key
ky a
y)
= (Key
kx Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
ky) Bool -> Bool -> Bool
|| (a
xa -> a -> Bool
forall a. Eq a => a -> a -> Bool
/=a
y)
nequal IntMap a
Nil IntMap a
Nil = Bool
False
nequal IntMap a
_ IntMap a
_ = Bool
True
#if MIN_VERSION_base(4,9,0)
instance Eq1 IntMap where
liftEq :: (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
liftEq a -> b -> Bool
eq (Bin Key
p1 Key
m1 IntMap a
l1 IntMap a
r1) (Bin Key
p2 Key
m2 IntMap b
l2 IntMap b
r2)
= (Key
m1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
m2) Bool -> Bool -> Bool
&& (Key
p1 Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p2) Bool -> Bool -> Bool
&& ((a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq IntMap a
l1 IntMap b
l2) Bool -> Bool -> Bool
&& ((a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq IntMap a
r1 IntMap b
r2)
liftEq a -> b -> Bool
eq (Tip Key
kx a
x) (Tip Key
ky b
y)
= (Key
kx Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
ky) Bool -> Bool -> Bool
&& (a -> b -> Bool
eq a
x b
y)
liftEq a -> b -> Bool
_eq IntMap a
Nil IntMap b
Nil = Bool
True
liftEq a -> b -> Bool
_eq IntMap a
_ IntMap b
_ = Bool
False
#endif
instance Ord a => Ord (IntMap a) where
compare :: IntMap a -> IntMap a -> Ordering
compare IntMap a
m1 IntMap a
m2 = [(Key, a)] -> [(Key, a)] -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toList IntMap a
m1) (IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toList IntMap a
m2)
#if MIN_VERSION_base(4,9,0)
instance Ord1 IntMap where
liftCompare :: (a -> b -> Ordering) -> IntMap a -> IntMap b -> Ordering
liftCompare a -> b -> Ordering
cmp IntMap a
m IntMap b
n =
((Key, a) -> (Key, b) -> Ordering)
-> [(Key, a)] -> [(Key, b)] -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare ((a -> b -> Ordering) -> (Key, a) -> (Key, b) -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp) (IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toList IntMap a
m) (IntMap b -> [(Key, b)]
forall a. IntMap a -> [(Key, a)]
toList IntMap b
n)
#endif
instance Functor IntMap where
fmap :: (a -> b) -> IntMap a -> IntMap b
fmap = (a -> b) -> IntMap a -> IntMap b
forall a b. (a -> b) -> IntMap a -> IntMap b
map
#ifdef __GLASGOW_HASKELL__
a
a <$ :: a -> IntMap b -> IntMap a
<$ Bin Key
p Key
m IntMap b
l IntMap b
r = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m (a
a a -> IntMap b -> IntMap a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ IntMap b
l) (a
a a -> IntMap b -> IntMap a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ IntMap b
r)
a
a <$ Tip Key
k b
_ = Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
k a
a
a
_ <$ IntMap b
Nil = IntMap a
forall a. IntMap a
Nil
#endif
instance Show a => Show (IntMap a) where
showsPrec :: Key -> IntMap a -> [Char] -> [Char]
showsPrec Key
d IntMap a
m = Bool -> ([Char] -> [Char]) -> [Char] -> [Char]
showParen (Key
d Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
10) (([Char] -> [Char]) -> [Char] -> [Char])
-> ([Char] -> [Char]) -> [Char] -> [Char]
forall a b. (a -> b) -> a -> b
$
[Char] -> [Char] -> [Char]
showString [Char]
"fromList " ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, a)] -> [Char] -> [Char]
forall a. Show a => a -> [Char] -> [Char]
shows (IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toList IntMap a
m)
#if MIN_VERSION_base(4,9,0)
instance Show1 IntMap where
liftShowsPrec :: (Key -> a -> [Char] -> [Char])
-> ([a] -> [Char] -> [Char]) -> Key -> IntMap a -> [Char] -> [Char]
liftShowsPrec Key -> a -> [Char] -> [Char]
sp [a] -> [Char] -> [Char]
sl Key
d IntMap a
m =
(Key -> [(Key, a)] -> [Char] -> [Char])
-> [Char] -> Key -> [(Key, a)] -> [Char] -> [Char]
forall a.
(Key -> a -> [Char] -> [Char])
-> [Char] -> Key -> a -> [Char] -> [Char]
showsUnaryWith ((Key -> (Key, a) -> [Char] -> [Char])
-> ([(Key, a)] -> [Char] -> [Char])
-> Key
-> [(Key, a)]
-> [Char]
-> [Char]
forall (f :: * -> *) a.
Show1 f =>
(Key -> a -> [Char] -> [Char])
-> ([a] -> [Char] -> [Char]) -> Key -> f a -> [Char] -> [Char]
liftShowsPrec Key -> (Key, a) -> [Char] -> [Char]
sp' [(Key, a)] -> [Char] -> [Char]
sl') [Char]
"fromList" Key
d (IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
toList IntMap a
m)
where
sp' :: Key -> (Key, a) -> [Char] -> [Char]
sp' = (Key -> a -> [Char] -> [Char])
-> ([a] -> [Char] -> [Char]) -> Key -> (Key, a) -> [Char] -> [Char]
forall (f :: * -> *) a.
Show1 f =>
(Key -> a -> [Char] -> [Char])
-> ([a] -> [Char] -> [Char]) -> Key -> f a -> [Char] -> [Char]
liftShowsPrec Key -> a -> [Char] -> [Char]
sp [a] -> [Char] -> [Char]
sl
sl' :: [(Key, a)] -> [Char] -> [Char]
sl' = (Key -> a -> [Char] -> [Char])
-> ([a] -> [Char] -> [Char]) -> [(Key, a)] -> [Char] -> [Char]
forall (f :: * -> *) a.
Show1 f =>
(Key -> a -> [Char] -> [Char])
-> ([a] -> [Char] -> [Char]) -> [f a] -> [Char] -> [Char]
liftShowList Key -> a -> [Char] -> [Char]
sp [a] -> [Char] -> [Char]
sl
#endif
instance (Read e) => Read (IntMap e) where
#ifdef __GLASGOW_HASKELL__
readPrec :: ReadPrec (IntMap e)
readPrec = ReadPrec (IntMap e) -> ReadPrec (IntMap e)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (IntMap e) -> ReadPrec (IntMap e))
-> ReadPrec (IntMap e) -> ReadPrec (IntMap e)
forall a b. (a -> b) -> a -> b
$ Key -> ReadPrec (IntMap e) -> ReadPrec (IntMap e)
forall a. Key -> ReadPrec a -> ReadPrec a
prec Key
10 (ReadPrec (IntMap e) -> ReadPrec (IntMap e))
-> ReadPrec (IntMap e) -> ReadPrec (IntMap e)
forall a b. (a -> b) -> a -> b
$ do
Ident [Char]
"fromList" <- ReadPrec Lexeme
lexP
[(Key, e)]
xs <- ReadPrec [(Key, e)]
forall a. Read a => ReadPrec a
readPrec
IntMap e -> ReadPrec (IntMap e)
forall (m :: * -> *) a. Monad m => a -> m a
return ([(Key, e)] -> IntMap e
forall a. [(Key, a)] -> IntMap a
fromList [(Key, e)]
xs)
readListPrec :: ReadPrec [IntMap e]
readListPrec = ReadPrec [IntMap e]
forall a. Read a => ReadPrec [a]
readListPrecDefault
#else
readsPrec p = readParen (p > 10) $ \ r -> do
("fromList",s) <- lex r
(xs,t) <- reads s
return (fromList xs,t)
#endif
#if MIN_VERSION_base(4,9,0)
instance Read1 IntMap where
liftReadsPrec :: (Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (IntMap a)
liftReadsPrec Key -> ReadS a
rp ReadS [a]
rl = ([Char] -> ReadS (IntMap a)) -> Key -> ReadS (IntMap a)
forall a. ([Char] -> ReadS a) -> Key -> ReadS a
readsData (([Char] -> ReadS (IntMap a)) -> Key -> ReadS (IntMap a))
-> ([Char] -> ReadS (IntMap a)) -> Key -> ReadS (IntMap a)
forall a b. (a -> b) -> a -> b
$
(Key -> ReadS [(Key, a)])
-> [Char] -> ([(Key, a)] -> IntMap a) -> [Char] -> ReadS (IntMap a)
forall a t.
(Key -> ReadS a) -> [Char] -> (a -> t) -> [Char] -> ReadS t
readsUnaryWith ((Key -> ReadS (Key, a))
-> ReadS [(Key, a)] -> Key -> ReadS [(Key, a)]
forall (f :: * -> *) a.
Read1 f =>
(Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (f a)
liftReadsPrec Key -> ReadS (Key, a)
rp' ReadS [(Key, a)]
rl') [Char]
"fromList" [(Key, a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
fromList
where
rp' :: Key -> ReadS (Key, a)
rp' = (Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (Key, a)
forall (f :: * -> *) a.
Read1 f =>
(Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (f a)
liftReadsPrec Key -> ReadS a
rp ReadS [a]
rl
rl' :: ReadS [(Key, a)]
rl' = (Key -> ReadS a) -> ReadS [a] -> ReadS [(Key, a)]
forall (f :: * -> *) a.
Read1 f =>
(Key -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadList Key -> ReadS a
rp ReadS [a]
rl
#endif
INSTANCE_TYPEABLE1(IntMap)
link :: Prefix -> IntMap a -> Prefix -> IntMap a -> IntMap a
link :: Key -> IntMap a -> Key -> IntMap a -> IntMap a
link Key
p1 IntMap a
t1 Key
p2 IntMap a
t2 = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
linkWithMask (Key -> Key -> Key
branchMask Key
p1 Key
p2) Key
p1 IntMap a
t1 IntMap a
t2
{-# INLINE link #-}
linkWithMask :: Mask -> Prefix -> IntMap a -> IntMap a -> IntMap a
linkWithMask :: Key -> Key -> IntMap a -> IntMap a -> IntMap a
linkWithMask Key
m Key
p1 IntMap a
t1 IntMap a
t2
| Key -> Key -> Bool
zero Key
p1 Key
m = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
t1 IntMap a
t2
| Bool
otherwise = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
t2 IntMap a
t1
where
p :: Key
p = Key -> Key -> Key
mask Key
p1 Key
m
{-# INLINE linkWithMask #-}
bin :: Prefix -> Mask -> IntMap a -> IntMap a -> IntMap a
bin :: Key -> Key -> IntMap a -> IntMap a -> IntMap a
bin Key
_ Key
_ IntMap a
l IntMap a
Nil = IntMap a
l
bin Key
_ Key
_ IntMap a
Nil IntMap a
r = IntMap a
r
bin Key
p Key
m IntMap a
l IntMap a
r = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l IntMap a
r
{-# INLINE bin #-}
binCheckLeft :: Prefix -> Mask -> IntMap a -> IntMap a -> IntMap a
binCheckLeft :: Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckLeft Key
_ Key
_ IntMap a
Nil IntMap a
r = IntMap a
r
binCheckLeft Key
p Key
m IntMap a
l IntMap a
r = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l IntMap a
r
{-# INLINE binCheckLeft #-}
binCheckRight :: Prefix -> Mask -> IntMap a -> IntMap a -> IntMap a
binCheckRight :: Key -> Key -> IntMap a -> IntMap a -> IntMap a
binCheckRight Key
_ Key
_ IntMap a
l IntMap a
Nil = IntMap a
l
binCheckRight Key
p Key
m IntMap a
l IntMap a
r = Key -> Key -> IntMap a -> IntMap a -> IntMap a
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m IntMap a
l IntMap a
r
{-# INLINE binCheckRight #-}
zero :: Key -> Mask -> Bool
zero :: Key -> Key -> Bool
zero Key
i Key
m
= (Key -> Nat
natFromInt Key
i) Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. (Key -> Nat
natFromInt Key
m) Nat -> Nat -> Bool
forall a. Eq a => a -> a -> Bool
== Nat
0
{-# INLINE zero #-}
nomatch,match :: Key -> Prefix -> Mask -> Bool
nomatch :: Key -> Key -> Key -> Bool
nomatch Key
i Key
p Key
m
= (Key -> Key -> Key
mask Key
i Key
m) Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
/= Key
p
{-# INLINE nomatch #-}
match :: Key -> Key -> Key -> Bool
match Key
i Key
p Key
m
= (Key -> Key -> Key
mask Key
i Key
m) Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== Key
p
{-# INLINE match #-}
mask :: Key -> Mask -> Prefix
mask :: Key -> Key -> Key
mask Key
i Key
m
= Nat -> Nat -> Key
maskW (Key -> Nat
natFromInt Key
i) (Key -> Nat
natFromInt Key
m)
{-# INLINE mask #-}
maskW :: Nat -> Nat -> Prefix
maskW :: Nat -> Nat -> Key
maskW Nat
i Nat
m
= Nat -> Key
intFromNat (Nat
i Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
.&. ((-Nat
m) Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
`xor` Nat
m))
{-# INLINE maskW #-}
shorter :: Mask -> Mask -> Bool
shorter :: Key -> Key -> Bool
shorter Key
m1 Key
m2
= (Key -> Nat
natFromInt Key
m1) Nat -> Nat -> Bool
forall a. Ord a => a -> a -> Bool
> (Key -> Nat
natFromInt Key
m2)
{-# INLINE shorter #-}
branchMask :: Prefix -> Prefix -> Mask
branchMask :: Key -> Key -> Key
branchMask Key
p1 Key
p2
= Nat -> Key
intFromNat (Nat -> Nat
highestBitMask (Key -> Nat
natFromInt Key
p1 Nat -> Nat -> Nat
forall a. Bits a => a -> a -> a
`xor` Key -> Nat
natFromInt Key
p2))
{-# INLINE branchMask #-}
splitRoot :: IntMap a -> [IntMap a]
splitRoot :: IntMap a -> [IntMap a]
splitRoot IntMap a
orig =
case IntMap a
orig of
IntMap a
Nil -> []
x :: IntMap a
x@(Tip Key
_ a
_) -> [IntMap a
x]
Bin Key
_ Key
m IntMap a
l IntMap a
r | Key
m Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
< Key
0 -> [IntMap a
r, IntMap a
l]
| Bool
otherwise -> [IntMap a
l, IntMap a
r]
{-# INLINE splitRoot #-}
showTree :: Show a => IntMap a -> String
showTree :: IntMap a -> [Char]
showTree IntMap a
s
= Bool -> Bool -> IntMap a -> [Char]
forall a. Show a => Bool -> Bool -> IntMap a -> [Char]
showTreeWith Bool
True Bool
False IntMap a
s
showTreeWith :: Show a => Bool -> Bool -> IntMap a -> String
showTreeWith :: Bool -> Bool -> IntMap a -> [Char]
showTreeWith Bool
hang Bool
wide IntMap a
t
| Bool
hang = (Bool -> [[Char]] -> IntMap a -> [Char] -> [Char]
forall a.
Show a =>
Bool -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTreeHang Bool
wide [] IntMap a
t) [Char]
""
| Bool
otherwise = (Bool -> [[Char]] -> [[Char]] -> IntMap a -> [Char] -> [Char]
forall a.
Show a =>
Bool -> [[Char]] -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTree Bool
wide [] [] IntMap a
t) [Char]
""
showsTree :: Show a => Bool -> [String] -> [String] -> IntMap a -> ShowS
showsTree :: Bool -> [[Char]] -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTree Bool
wide [[Char]]
lbars [[Char]]
rbars IntMap a
t = case IntMap a
t of
Bin Key
p Key
m IntMap a
l IntMap a
r ->
Bool -> [[Char]] -> [[Char]] -> IntMap a -> [Char] -> [Char]
forall a.
Show a =>
Bool -> [[Char]] -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTree Bool
wide ([[Char]] -> [[Char]]
withBar [[Char]]
rbars) ([[Char]] -> [[Char]]
withEmpty [[Char]]
rbars) IntMap a
r ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> [Char] -> [Char]
showWide Bool
wide [[Char]]
rbars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[[Char]] -> [Char] -> [Char]
showsBars [[Char]]
lbars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString (Key -> Key -> [Char]
showBin Key
p Key
m) ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
"\n" ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> [Char] -> [Char]
showWide Bool
wide [[Char]]
lbars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> [[Char]] -> IntMap a -> [Char] -> [Char]
forall a.
Show a =>
Bool -> [[Char]] -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTree Bool
wide ([[Char]] -> [[Char]]
withEmpty [[Char]]
lbars) ([[Char]] -> [[Char]]
withBar [[Char]]
lbars) IntMap a
l
Tip Key
k a
x ->
[[Char]] -> [Char] -> [Char]
showsBars [[Char]]
lbars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> [Char] -> [Char]
showString [Char]
" " ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> [Char] -> [Char]
forall a. Show a => a -> [Char] -> [Char]
shows Key
k ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
":=" ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Char] -> [Char]
forall a. Show a => a -> [Char] -> [Char]
shows a
x ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
"\n"
IntMap a
Nil -> [[Char]] -> [Char] -> [Char]
showsBars [[Char]]
lbars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
"|\n"
showsTreeHang :: Show a => Bool -> [String] -> IntMap a -> ShowS
showsTreeHang :: Bool -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTreeHang Bool
wide [[Char]]
bars IntMap a
t = case IntMap a
t of
Bin Key
p Key
m IntMap a
l IntMap a
r ->
[[Char]] -> [Char] -> [Char]
showsBars [[Char]]
bars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString (Key -> Key -> [Char]
showBin Key
p Key
m) ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
"\n" ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> [Char] -> [Char]
showWide Bool
wide [[Char]]
bars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> IntMap a -> [Char] -> [Char]
forall a.
Show a =>
Bool -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTreeHang Bool
wide ([[Char]] -> [[Char]]
withBar [[Char]]
bars) IntMap a
l ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> [Char] -> [Char]
showWide Bool
wide [[Char]]
bars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
Bool -> [[Char]] -> IntMap a -> [Char] -> [Char]
forall a.
Show a =>
Bool -> [[Char]] -> IntMap a -> [Char] -> [Char]
showsTreeHang Bool
wide ([[Char]] -> [[Char]]
withEmpty [[Char]]
bars) IntMap a
r
Tip Key
k a
x ->
[[Char]] -> [Char] -> [Char]
showsBars [[Char]]
bars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
.
[Char] -> [Char] -> [Char]
showString [Char]
" " ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> [Char] -> [Char]
forall a. Show a => a -> [Char] -> [Char]
shows Key
k ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
":=" ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. a -> [Char] -> [Char]
forall a. Show a => a -> [Char] -> [Char]
shows a
x ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
"\n"
IntMap a
Nil -> [[Char]] -> [Char] -> [Char]
showsBars [[Char]]
bars ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
"|\n"
showBin :: Prefix -> Mask -> String
showBin :: Key -> Key -> [Char]
showBin Key
_ Key
_
= [Char]
"*"
showWide :: Bool -> [String] -> String -> String
showWide :: Bool -> [[Char]] -> [Char] -> [Char]
showWide Bool
wide [[Char]]
bars
| Bool
wide = [Char] -> [Char] -> [Char]
showString ([[Char]] -> [Char]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Char]] -> [[Char]]
forall a. [a] -> [a]
reverse [[Char]]
bars)) ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
"|\n"
| Bool
otherwise = [Char] -> [Char]
forall a. a -> a
id
showsBars :: [String] -> ShowS
showsBars :: [[Char]] -> [Char] -> [Char]
showsBars [[Char]]
bars
= case [[Char]]
bars of
[] -> [Char] -> [Char]
forall a. a -> a
id
[[Char]]
_ -> [Char] -> [Char] -> [Char]
showString ([[Char]] -> [Char]
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat ([[Char]] -> [[Char]]
forall a. [a] -> [a]
reverse ([[Char]] -> [[Char]]
forall a. [a] -> [a]
tail [[Char]]
bars))) ([Char] -> [Char]) -> ([Char] -> [Char]) -> [Char] -> [Char]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Char] -> [Char] -> [Char]
showString [Char]
node
node :: String
node :: [Char]
node = [Char]
"+--"
withBar, withEmpty :: [String] -> [String]
withBar :: [[Char]] -> [[Char]]
withBar [[Char]]
bars = [Char]
"| "[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:[[Char]]
bars
withEmpty :: [[Char]] -> [[Char]]
withEmpty [[Char]]
bars = [Char]
" "[Char] -> [[Char]] -> [[Char]]
forall a. a -> [a] -> [a]
:[[Char]]
bars