{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternGuards #-}
#include "containers.h"
module Data.IntMap.Strict.Internal (
#if !defined(TESTING)
IntMap, Key
#else
IntMap(..), Key
#endif
, empty
, singleton
, fromSet
, fromList
, fromListWith
, fromListWithKey
, fromAscList
, fromAscListWith
, fromAscListWithKey
, fromDistinctAscList
, insert
, insertWith
, insertWithKey
, insertLookupWithKey
, delete
, adjust
, adjustWithKey
, update
, updateWithKey
, updateLookupWithKey
, alter
, alterF
, lookup
, (!?)
, (!)
, findWithDefault
, member
, notMember
, lookupLT
, lookupGT
, lookupLE
, lookupGE
, null
, size
, union
, unionWith
, unionWithKey
, unions
, unionsWith
, difference
, (\\)
, differenceWith
, differenceWithKey
, intersection
, intersectionWith
, intersectionWithKey
, disjoint
, compose
, mergeWithKey
, map
, mapWithKey
, traverseWithKey
, traverseMaybeWithKey
, mapAccum
, mapAccumWithKey
, mapAccumRWithKey
, mapKeys
, mapKeysWith
, mapKeysMonotonic
, foldr
, foldl
, foldrWithKey
, foldlWithKey
, foldMapWithKey
, foldr'
, foldl'
, foldrWithKey'
, foldlWithKey'
, elems
, keys
, assocs
, keysSet
, toList
, toAscList
, toDescList
, filter
, filterWithKey
, restrictKeys
, withoutKeys
, partition
, partitionWithKey
, mapMaybe
, mapMaybeWithKey
, mapEither
, mapEitherWithKey
, split
, splitLookup
, splitRoot
, isSubmapOf, isSubmapOfBy
, isProperSubmapOf, isProperSubmapOfBy
, lookupMin
, lookupMax
, findMin
, findMax
, deleteMin
, deleteMax
, deleteFindMin
, deleteFindMax
, updateMin
, updateMax
, updateMinWithKey
, updateMaxWithKey
, minView
, maxView
, minViewWithKey
, maxViewWithKey
#ifdef __GLASGOW_HASKELL__
, showTree
, showTreeWith
#endif
) where
import Prelude hiding (lookup,map,filter,foldr,foldl,null)
import Data.Bits
import qualified Data.IntMap.Internal as L
import Data.IntMap.Internal
( IntMap (..)
, Key
, mask
, branchMask
, nomatch
, zero
, natFromInt
, intFromNat
, bin
, binCheckLeft
, binCheckRight
, link
, linkWithMask
, (\\)
, (!)
, (!?)
, empty
, assocs
, filter
, filterWithKey
, findMin
, findMax
, foldMapWithKey
, foldr
, foldl
, foldr'
, foldl'
, foldlWithKey
, foldrWithKey
, foldlWithKey'
, foldrWithKey'
, keysSet
, mergeWithKey'
, compose
, delete
, deleteMin
, deleteMax
, deleteFindMax
, deleteFindMin
, difference
, elems
, intersection
, disjoint
, isProperSubmapOf
, isProperSubmapOfBy
, isSubmapOf
, isSubmapOfBy
, lookup
, lookupLE
, lookupGE
, lookupLT
, lookupGT
, lookupMin
, lookupMax
, minView
, maxView
, minViewWithKey
, maxViewWithKey
, keys
, mapKeys
, mapKeysMonotonic
, member
, notMember
, null
, partition
, partitionWithKey
, restrictKeys
, size
, split
, splitLookup
, splitRoot
, toAscList
, toDescList
, toList
, union
, unions
, withoutKeys
)
#ifdef __GLASGOW_HASKELL__
import Data.IntMap.Internal.DeprecatedDebug (showTree, showTreeWith)
#endif
import qualified Data.IntSet.Internal as IntSet
import Utils.Containers.Internal.BitUtil
import Utils.Containers.Internal.StrictPair
#if !MIN_VERSION_base(4,8,0)
import Data.Functor((<$>))
#endif
import Control.Applicative (Applicative (..), liftA2)
import qualified Data.Foldable as Foldable
#if !MIN_VERSION_base(4,8,0)
import Data.Foldable (Foldable())
#endif
findWithDefault :: a -> Key -> IntMap a -> a
findWithDefault :: forall a. 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
singleton :: Key -> a -> IntMap a
singleton :: forall a. 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 :: forall a. Key -> a -> IntMap a -> IntMap a
insert !Key
k !a
x IntMap a
t =
case IntMap a
t of
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)
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
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 :: forall a. (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 :: 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 =
case IntMap a
t of
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
singleton 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)
Tip Key
ky a
y
| 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 -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! 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
singleton Key
k a
x) Key
ky IntMap a
t
IntMap a
Nil -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
singleton Key
k a
x
insertLookupWithKey :: (Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a)
insertLookupWithKey :: forall a.
(Key -> a -> a -> a) -> Key -> a -> IntMap a -> (Maybe a, IntMap a)
insertLookupWithKey Key -> a -> a -> a
f0 !Key
k0 a
x0 IntMap a
t0 = StrictPair (Maybe a) (IntMap a) -> (Maybe a, IntMap a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Maybe a) (IntMap a) -> (Maybe a, IntMap a))
-> StrictPair (Maybe a) (IntMap a) -> (Maybe a, IntMap a)
forall a b. (a -> b) -> a -> b
$ (Key -> a -> a -> a)
-> Key -> a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall {a}.
(Key -> a -> a -> a)
-> Key -> a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> a -> a
f0 Key
k0 a
x0 IntMap a
t0
where
go :: (Key -> a -> a -> a)
-> Key -> a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> a -> a
f Key
k a
x IntMap a
t =
case IntMap a
t of
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 Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: 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
singleton 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 -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> a -> a
f Key
k a
x IntMap a
l in (Maybe a
found Maybe a -> IntMap a -> StrictPair (Maybe 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
l' IntMap a
r)
| Bool
otherwise -> let (Maybe a
found :*: IntMap a
r') = (Key -> a -> a -> a)
-> Key -> a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> a -> a
f Key
k a
x IntMap a
r in (Maybe a
found Maybe a -> IntMap a -> StrictPair (Maybe 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
l IntMap a
r')
Tip Key
ky a
y
| Key
kKey -> Key -> Bool
forall a. Eq a => a -> a -> Bool
==Key
ky -> (a -> Maybe a
forall a. a -> Maybe a
Just a
y Maybe a -> IntMap a -> StrictPair (Maybe 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 -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! Key -> a -> a -> a
f Key
k a
x a
y))
| Bool
otherwise -> (Maybe a
forall a. Maybe a
Nothing Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: 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
singleton Key
k a
x) Key
ky IntMap a
t)
IntMap a
Nil -> Maybe a
forall a. Maybe a
Nothing Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: (Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
singleton Key
k a
x)
adjust :: (a -> a) -> Key -> IntMap a -> IntMap a
adjust :: forall a. (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 :: forall a. (Key -> a -> a) -> Key -> IntMap a -> IntMap a
adjustWithKey Key -> a -> a
f !Key
k IntMap a
t =
case IntMap a
t of
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)
Tip Key
ky a
y
| 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
ky (a -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! Key -> a -> a
f Key
k a
y
| Bool
otherwise -> IntMap a
t
IntMap a
Nil -> IntMap a
forall a. IntMap a
Nil
update :: (a -> Maybe a) -> Key -> IntMap a -> IntMap a
update :: forall a. (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 :: forall a. (Key -> a -> Maybe a) -> Key -> IntMap a -> IntMap a
updateWithKey Key -> a -> Maybe a
f !Key
k IntMap a
t =
case IntMap a
t of
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)
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' -> 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
IntMap a
Nil -> IntMap a
forall a. IntMap a
Nil
updateLookupWithKey :: (Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a,IntMap a)
updateLookupWithKey :: forall a.
(Key -> a -> Maybe a) -> Key -> IntMap a -> (Maybe a, IntMap a)
updateLookupWithKey Key -> a -> Maybe a
f0 !Key
k0 IntMap a
t0 = StrictPair (Maybe a) (IntMap a) -> (Maybe a, IntMap a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Maybe a) (IntMap a) -> (Maybe a, IntMap a))
-> StrictPair (Maybe a) (IntMap a) -> (Maybe a, IntMap a)
forall a b. (a -> b) -> a -> b
$ (Key -> a -> Maybe a)
-> Key -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall {a}.
(Key -> a -> Maybe a)
-> Key -> IntMap a -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> Maybe a
f0 Key
k0 IntMap a
t0
where
go :: (Key -> a -> Maybe a)
-> Key -> IntMap a -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> Maybe a
f Key
k IntMap a
t =
case IntMap a
t of
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 Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: 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 -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> Maybe a
f Key
k IntMap a
l in (Maybe a
found Maybe a -> IntMap a -> StrictPair (Maybe 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
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 -> StrictPair (Maybe a) (IntMap a)
go Key -> a -> Maybe a
f Key
k IntMap a
r in (Maybe a
found Maybe a -> IntMap a -> StrictPair (Maybe 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
binCheckRight Key
p Key
m IntMap a
l IntMap a
r')
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 Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: 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 Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
| Bool
otherwise -> (Maybe a
forall a. Maybe a
Nothing Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
t)
IntMap a
Nil -> (Maybe a
forall a. Maybe a
Nothing Maybe a -> IntMap a -> StrictPair (Maybe a) (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
alter :: (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
alter :: forall a. (Maybe a -> Maybe a) -> Key -> IntMap a -> IntMap a
alter Maybe a -> Maybe a
f !Key
k IntMap a
t =
case IntMap a
t of
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)
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 -> IntMap a
t
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 :: forall (f :: * -> *) a.
Functor f =>
(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
unionsWith :: Foldable f => (a->a->a) -> f (IntMap a) -> IntMap a
unionsWith :: forall (f :: * -> *) a.
Foldable f =>
(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
unionWith :: (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
unionWith :: forall a. (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 :: forall a. (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 (a -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! 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
differenceWith :: (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
differenceWith :: forall a b. (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 :: forall a b.
(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
intersectionWith :: (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
intersectionWith :: forall a b c. (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 :: forall a b c.
(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 (c -> IntMap c) -> c -> IntMap c
forall a b. (a -> b) -> a -> b
$! 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 :: 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 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 #-}
updateMinWithKey :: (Key -> a -> Maybe a) -> IntMap a -> IntMap a
updateMinWithKey :: forall a. (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 a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
go Key -> a -> Maybe a
f IntMap a
r)
IntMap a
_ -> (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
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 :: forall a. (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 a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
go Key -> a -> Maybe a
f IntMap a
l) IntMap a
r
IntMap a
_ -> (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
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"
updateMax :: (a -> Maybe a) -> IntMap a -> IntMap a
updateMax :: forall a. (a -> Maybe a) -> IntMap a -> IntMap a
updateMax a -> Maybe a
f = (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
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 :: forall a. (a -> Maybe a) -> IntMap a -> IntMap a
updateMin a -> Maybe a
f = (Key -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Key -> a -> Maybe a) -> IntMap a -> IntMap a
updateMinWithKey ((a -> Maybe a) -> Key -> a -> Maybe a
forall a b. a -> b -> a
const a -> Maybe a
f)
map :: (a -> b) -> IntMap a -> IntMap b
map :: forall a b. (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 (b -> IntMap b) -> b -> IntMap b
forall a b. (a -> b) -> a -> b
$! 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 (\x -> f $! g x) xs
"map/mapL" forall f g xs . map f (L.map g xs) = map (\x -> f (g x)) xs
#-}
#endif
mapWithKey :: (Key -> a -> b) -> IntMap a -> IntMap b
mapWithKey :: forall a b. (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 (b -> IntMap b) -> b -> IntMap b
forall a b. (a -> b) -> a -> b
$! 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/mapWithKeyL" forall f g xs . mapWithKey f (L.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
"mapWithKey/mapL" forall f g xs . mapWithKey f (L.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
"map/mapWithKeyL" forall f g xs . map f (L.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 :: forall (t :: * -> *) a b.
Applicative t =>
(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) = (\ !b
v' -> Key -> b -> IntMap b
forall a. Key -> a -> IntMap a
Tip Key
k b
v') (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 #-}
traverseMaybeWithKey
:: Applicative f => (Key -> a -> f (Maybe b)) -> IntMap a -> f (IntMap b)
traverseMaybeWithKey :: forall (f :: * -> *) a b.
Applicative f =>
(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 (b -> IntMap b) -> b -> IntMap b
forall a b. (a -> b) -> a -> b
$!) (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)
mapAccum :: (a -> b -> (a,c)) -> a -> IntMap b -> (a,IntMap c)
mapAccum :: forall a b c. (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 :: forall a b c.
(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 :: forall a b c.
(a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
mapAccumL a -> Key -> b -> (a, c)
f0 a
a0 IntMap b
t0 = StrictPair a (IntMap c) -> (a, IntMap c)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair a (IntMap c) -> (a, IntMap c))
-> StrictPair a (IntMap c) -> (a, IntMap c)
forall a b. (a -> b) -> a -> b
$ (a -> Key -> b -> (a, c))
-> a -> IntMap b -> StrictPair a (IntMap c)
forall {a} {a} {a}.
(a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> b -> (a, c)
f0 a
a0 IntMap b
t0
where
go :: (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a 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 ->
let (a
a1 :*: IntMap a
r') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a IntMap a
r
(a
a2 :*: IntMap a
l') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a1 IntMap a
l
in (a
a2 a -> IntMap a -> StrictPair 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
l' IntMap a
r')
| Bool
otherwise ->
let (a
a1 :*: IntMap a
l') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a IntMap a
l
(a
a2 :*: IntMap a
r') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a1 IntMap a
r
in (a
a2 a -> IntMap a -> StrictPair 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
l' IntMap a
r')
Tip Key
k a
x -> let !(a
a',!a
x') = a -> Key -> a -> (a, a)
f a
a Key
k a
x in (a
a' a -> IntMap a -> StrictPair 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
x')
IntMap a
Nil -> (a
a a -> IntMap a -> StrictPair a (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
mapAccumRWithKey :: (a -> Key -> b -> (a,c)) -> a -> IntMap b -> (a,IntMap c)
mapAccumRWithKey :: forall a b c.
(a -> Key -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
mapAccumRWithKey a -> Key -> b -> (a, c)
f0 a
a0 IntMap b
t0 = StrictPair a (IntMap c) -> (a, IntMap c)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair a (IntMap c) -> (a, IntMap c))
-> StrictPair a (IntMap c) -> (a, IntMap c)
forall a b. (a -> b) -> a -> b
$ (a -> Key -> b -> (a, c))
-> a -> IntMap b -> StrictPair a (IntMap c)
forall {a} {a} {a}.
(a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> b -> (a, c)
f0 a
a0 IntMap b
t0
where
go :: (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a 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 ->
let (a
a1 :*: IntMap a
l') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a IntMap a
l
(a
a2 :*: IntMap a
r') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a1 IntMap a
r
in (a
a2 a -> IntMap a -> StrictPair 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
l' IntMap a
r')
| Bool
otherwise ->
let (a
a1 :*: IntMap a
r') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a IntMap a
r
(a
a2 :*: IntMap a
l') = (a -> Key -> a -> (a, a))
-> a -> IntMap a -> StrictPair a (IntMap a)
go a -> Key -> a -> (a, a)
f a
a1 IntMap a
l
in (a
a2 a -> IntMap a -> StrictPair 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
l' IntMap a
r')
Tip Key
k a
x -> let !(a
a',!a
x') = a -> Key -> a -> (a, a)
f a
a Key
k a
x in (a
a' a -> IntMap a -> StrictPair 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
x')
IntMap a
Nil -> (a
a a -> IntMap a -> StrictPair a (IntMap a)
forall a b. a -> b -> StrictPair a b
:*: IntMap a
forall a. IntMap a
Nil)
mapKeysWith :: (a -> a -> a) -> (Key->Key) -> IntMap a -> IntMap a
mapKeysWith :: forall a. (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) []
mapMaybe :: (a -> Maybe b) -> IntMap a -> IntMap b
mapMaybe :: forall a b. (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 :: forall a b. (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 :: forall a b c. (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 :: forall a b c.
(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)
fromSet :: (Key -> a) -> IntSet.IntSet -> IntMap a
fromSet :: forall a. (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 BitMap
bm) = (Key -> a) -> Key -> BitMap -> Key -> IntMap a
forall {a}. (Key -> a) -> Key -> BitMap -> Key -> IntMap a
buildTree Key -> a
f Key
kx BitMap
bm (Key
IntSet.suffixBitMask Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
1)
where
buildTree :: (Key -> a) -> Key -> BitMap -> Key -> IntMap a
buildTree Key -> a
g !Key
prefix !BitMap
bmask Key
bits = case Key
bits of
Key
0 -> Key -> a -> IntMap a
forall a. Key -> a -> IntMap a
Tip Key
prefix (a -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! Key -> a
g Key
prefix
Key
_ -> case BitMap -> Key
intFromNat ((Key -> BitMap
natFromInt Key
bits) BitMap -> Key -> BitMap
`shiftRL` Key
1) of
Key
bits2 | BitMap
bmask BitMap -> BitMap -> BitMap
forall a. Bits a => a -> a -> a
.&. ((BitMap
1 BitMap -> Key -> BitMap
`shiftLL` Key
bits2) BitMap -> BitMap -> BitMap
forall a. Num a => a -> a -> a
- BitMap
1) BitMap -> BitMap -> Bool
forall a. Eq a => a -> a -> Bool
== BitMap
0 ->
(Key -> a) -> Key -> BitMap -> Key -> IntMap a
buildTree Key -> a
g (Key
prefix Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
bits2) (BitMap
bmask BitMap -> Key -> BitMap
`shiftRL` Key
bits2) Key
bits2
| (BitMap
bmask BitMap -> Key -> BitMap
`shiftRL` Key
bits2) BitMap -> BitMap -> BitMap
forall a. Bits a => a -> a -> a
.&. ((BitMap
1 BitMap -> Key -> BitMap
`shiftLL` Key
bits2) BitMap -> BitMap -> BitMap
forall a. Num a => a -> a -> a
- BitMap
1) BitMap -> BitMap -> Bool
forall a. Eq a => a -> a -> Bool
== BitMap
0 ->
(Key -> a) -> Key -> BitMap -> Key -> IntMap a
buildTree Key -> a
g Key
prefix BitMap
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 -> BitMap -> Key -> IntMap a
buildTree Key -> a
g Key
prefix BitMap
bmask Key
bits2) ((Key -> a) -> Key -> BitMap -> Key -> IntMap a
buildTree Key -> a
g (Key
prefix Key -> Key -> Key
forall a. Num a => a -> a -> a
+ Key
bits2) (BitMap
bmask BitMap -> Key -> BitMap
`shiftRL` Key
bits2) Key
bits2)
fromList :: [(Key,a)] -> IntMap a
fromList :: forall a. [(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 :: forall a. (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 :: forall a. (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 :: forall a. [(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 :: forall a. (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 :: forall a. (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 :: forall a. [(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 :: forall a.
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 -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! 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 -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! 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 -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! 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 -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! 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 -> IntMap a) -> a -> IntMap a
forall a b. (a -> b) -> a -> b
$! 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