{-# LANGUAGE CPP #-}
{-# LANGUAGE BangPatterns #-}
{-# LANGUAGE PatternGuards #-}
#if __GLASGOW_HASKELL__
{-# LANGUAGE DeriveDataTypeable, StandaloneDeriving #-}
#endif
#if defined(__GLASGOW_HASKELL__)
{-# LANGUAGE Trustworthy #-}
#endif
#if __GLASGOW_HASKELL__ >= 708
{-# LANGUAGE RoleAnnotations #-}
{-# LANGUAGE TypeFamilies #-}
#define USE_MAGIC_PROXY 1
#endif
#ifdef USE_MAGIC_PROXY
{-# LANGUAGE MagicHash #-}
#endif
{-# OPTIONS_HADDOCK not-home #-}
#include "containers.h"
#if !(WORD_SIZE_IN_BITS >= 61)
#define DEFINE_ALTERF_FALLBACK 1
#endif
module Data.Map.Internal (
Map(..)
, Size
, (!), (!?), (\\)
, null
, size
, member
, notMember
, lookup
, findWithDefault
, lookupLT
, lookupGT
, lookupLE
, lookupGE
, 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
, disjoint
, SimpleWhenMissing
, SimpleWhenMatched
, runWhenMatched
, runWhenMissing
, merge
, zipWithMaybeMatched
, zipWithMatched
, mapMaybeMissing
, dropMissing
, preserveMissing
, preserveMissing'
, mapMissing
, filterMissing
, WhenMissing (..)
, WhenMatched (..)
, mergeA
, zipWithMaybeAMatched
, zipWithAMatched
, traverseMaybeMissing
, traverseMissing
, filterAMissing
, 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
, fromDescList
, fromDescListWith
, fromDescListWithKey
, fromDistinctDescList
, filter
, filterWithKey
, takeWhileAntitone
, dropWhileAntitone
, spanAntitone
, restrictKeys
, withoutKeys
, partition
, partitionWithKey
, mapMaybe
, mapMaybeWithKey
, mapEither
, mapEitherWithKey
, split
, splitLookup
, splitRoot
, isSubmapOf, isSubmapOfBy
, isProperSubmapOf, isProperSubmapOfBy
, lookupIndex
, findIndex
, elemAt
, updateAt
, deleteAt
, take
, drop
, splitAt
, lookupMin
, lookupMax
, findMin
, findMax
, deleteMin
, deleteMax
, deleteFindMin
, deleteFindMax
, updateMin
, updateMax
, updateMinWithKey
, updateMaxWithKey
, minView
, maxView
, minViewWithKey
, maxViewWithKey
, AreWeStrict (..)
, atKeyImpl
#if __GLASGOW_HASKELL__ && MIN_VERSION_base(4,8,0)
, atKeyPlain
#endif
, bin
, balance
, balanceL
, balanceR
, delta
, insertMax
, link
, link2
, glue
, MaybeS(..)
, Identity(..)
, mapWhenMissing
, mapWhenMatched
, lmapWhenMissing
, contramapFirstWhenMatched
, contramapSecondWhenMatched
, mapGentlyWhenMissing
, mapGentlyWhenMatched
) where
#if MIN_VERSION_base(4,8,0)
import Data.Functor.Identity (Identity (..))
import Control.Applicative (liftA3)
#else
import Control.Applicative (Applicative(..), (<$>), liftA3)
import Data.Monoid (Monoid(..))
import Data.Traversable (Traversable(traverse))
#endif
#if MIN_VERSION_base(4,9,0)
import Data.Functor.Classes
import Data.Semigroup (stimesIdempotentMonoid)
#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
import Control.Applicative (Const (..))
import Control.DeepSeq (NFData(rnf))
import Data.Bits (shiftL, shiftR)
import qualified Data.Foldable as Foldable
#if !MIN_VERSION_base(4,8,0)
import Data.Foldable (Foldable())
#endif
import Data.Typeable
import Prelude hiding (lookup, map, filter, foldr, foldl, null, splitAt, take, drop)
import qualified Data.Set.Internal as Set
import Data.Set.Internal (Set)
import Utils.Containers.Internal.PtrEquality (ptrEq)
import Utils.Containers.Internal.StrictPair
import Utils.Containers.Internal.StrictMaybe
import Utils.Containers.Internal.BitQueue
#ifdef DEFINE_ALTERF_FALLBACK
import Utils.Containers.Internal.BitUtil (wordSize)
#endif
#if __GLASGOW_HASKELL__
import GHC.Exts (build, lazy)
#if !MIN_VERSION_base(4,8,0)
import Data.Functor ((<$))
#endif
#ifdef USE_MAGIC_PROXY
import GHC.Exts (Proxy#, proxy# )
#endif
#if __GLASGOW_HASKELL__ >= 708
import qualified GHC.Exts as GHCExts
#endif
import Text.Read hiding (lift)
import Data.Data
import qualified Control.Category as Category
#endif
#if __GLASGOW_HASKELL__ >= 708
import Data.Coerce
#endif
infixl 9 !,!?,\\
(!) :: Ord k => Map k a -> k -> a
! :: Map k a -> k -> a
(!) Map k a
m k
k = k -> Map k a -> a
forall k a. Ord k => k -> Map k a -> a
Evidence bound by a type signature of the constraint type Ord k
find k
k Map k a
m
#if __GLASGOW_HASKELL__
{-# INLINE (!) #-}
#endif
(!?) :: Ord k => Map k a -> k -> Maybe a
!? :: Map k a -> k -> Maybe a
(!?) Map k a
m k
k = k -> Map k a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
Evidence bound by a type signature of the constraint type Ord k
lookup k
k Map k a
m
#if __GLASGOW_HASKELL__
{-# INLINE (!?) #-}
#endif
(\\) :: Ord k => Map k a -> Map k b -> Map k a
Map k a
m1 \\ :: Map k a -> Map k b -> Map k a
\\ Map k b
m2 = Map k a -> Map k b -> Map k a
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Evidence bound by a type signature of the constraint type Ord k
difference Map k a
m1 Map k b
m2
#if __GLASGOW_HASKELL__
{-# INLINE (\\) #-}
#endif
data Map k a = Bin {-# UNPACK #-} !Size !k a !(Map k a) !(Map k a)
| Tip
type Size = Int
#if __GLASGOW_HASKELL__ >= 708
type role Map nominal representational
#endif
instance (Ord k) => Monoid (Map k v) where
mempty :: Map k v
mempty = Map k v
forall k a. Map k a
empty
mconcat :: [Map k v] -> Map k v
mconcat = [Map k v] -> Map k v
forall (f :: * -> *) k a.
(Foldable f, Ord k) =>
f (Map k a) -> Map k a
Evidence bound by a type signature of the constraint type Ord k
External instance of the constraint type Foldable []
unions
#if !(MIN_VERSION_base(4,9,0))
mappend = union
#else
mappend :: Map k v -> Map k v -> Map k v
mappend = Map k v -> Map k v -> Map k v
forall a. Semigroup a => a -> a -> a
Instance of class: Semigroup of the constraint type forall {k} {v}. Ord k => Semigroup (Map k v)
Evidence bound by a type signature of the constraint type Ord k
(<>)
instance (Ord k) => Semigroup (Map k v) where
<> :: Map k v -> Map k v -> Map k v
(<>) = Map k v -> Map k v -> Map k v
forall k v. Ord k => Map k v -> Map k v -> Map k v
Evidence bound by a type signature of the constraint type Ord k
union
stimes :: b -> Map k v -> Map k v
stimes = b -> Map k v -> Map k v
forall b a. (Integral b, Monoid a) => b -> a -> a
Instance of class: Monoid of the constraint type forall k v. Ord k => Monoid (Map k v)
Evidence bound by a type signature of the constraint type Ord k
Evidence bound by a type signature of the constraint type Integral b
stimesIdempotentMonoid
#endif
#if __GLASGOW_HASKELL__
instance (Data k, Data a, Ord k) => Data (Map k a) where
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Map k a -> c (Map k a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z Map k a
m = ([(k, a)] -> Map k a) -> c ([(k, a)] -> Map k a)
forall g. g -> c g
z [(k, a)] -> Map k a
forall k a. Ord k => [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k
fromList c ([(k, a)] -> Map k a) -> [(k, a)] -> c (Map k a)
forall d b. Data d => c (d -> b) -> d -> c b
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
Evidence bound by a type signature of the constraint type Data k
Evidence bound by a type signature of the constraint type Data a
`f` Map k a -> [(k, a)]
forall k a. Map k a -> [(k, a)]
toList Map k a
m
toConstr :: Map k a -> Constr
toConstr Map k a
_ = Constr
fromListConstr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Map k a)
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c = case Constr -> Int
constrIndex Constr
c of
Int
1 -> c ([(k, a)] -> Map k a) -> c (Map k a)
forall b r. Data b => c (b -> r) -> c r
External instance of the constraint type forall a. Data a => Data [a]
External instance of the constraint type forall a b. (Data a, Data b) => Data (a, b)
Evidence bound by a type signature of the constraint type Data k
Evidence bound by a type signature of the constraint type Data a
k (([(k, a)] -> Map k a) -> c ([(k, a)] -> Map k a)
forall r. r -> c r
z [(k, a)] -> Map k a
forall k a. Ord k => [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k
fromList)
Int
_ -> [Char] -> c (Map k a)
forall a. HasCallStack => [Char] -> a
error [Char]
"gunfold"
dataTypeOf :: Map k a -> DataType
dataTypeOf Map k a
_ = DataType
mapDataType
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Map k a))
dataCast2 forall d e. (Data d, Data e) => c (t d e)
f = c (t k a) -> Maybe (c (Map k a))
forall {k1} {k2} {k3} (c :: k1 -> *) (t :: k2 -> k3 -> k1)
(t' :: k2 -> k3 -> k1) (a :: k2) (b :: k3).
(Typeable t, Typeable t') =>
c (t a b) -> Maybe (c (t' a b))
Evidence bound by a type signature of the constraint type Typeable t
gcast2 c (t k a)
forall d e. (Data d, Data e) => c (t d e)
Evidence bound by a type signature of the constraint type Data a
Evidence bound by a type signature of the constraint type Data k
f
fromListConstr :: Constr
fromListConstr :: Constr
fromListConstr = DataType -> [Char] -> [[Char]] -> Fixity -> Constr
mkConstr DataType
mapDataType [Char]
"fromList" [] Fixity
Prefix
mapDataType :: DataType
mapDataType :: DataType
mapDataType = [Char] -> [Constr] -> DataType
mkDataType [Char]
"Data.Map.Internal.Map" [Constr
fromListConstr]
#endif
null :: Map k a -> Bool
null :: Map k a -> Bool
null Map k a
Tip = Bool
True
null (Bin {}) = Bool
False
{-# INLINE null #-}
size :: Map k a -> Int
size :: Map k a -> Int
size Map k a
Tip = Int
0
size (Bin Int
sz k
_ a
_ Map k a
_ Map k a
_) = Int
sz
{-# INLINE size #-}
lookup :: Ord k => k -> Map k a -> Maybe a
lookup :: k -> Map k a -> Maybe a
lookup = k -> Map k a -> Maybe a
forall k a. Ord k => k -> Map k a -> Maybe a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: t -> Map t a -> Maybe a
go !t
_ Map t a
Tip = Maybe a
forall a. Maybe a
Nothing
go t
k (Bin Int
_ t
kx a
x Map t a
l Map t a
r) = case t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord t
compare t
k t
kx of
Ordering
LT -> t -> Map t a -> Maybe a
go t
k Map t a
l
Ordering
GT -> t -> Map t a -> Maybe a
go t
k Map t a
r
Ordering
EQ -> a -> Maybe a
forall a. a -> Maybe a
Just a
x
#if __GLASGOW_HASKELL__
{-# INLINABLE lookup #-}
#else
{-# INLINE lookup #-}
#endif
member :: Ord k => k -> Map k a -> Bool
member :: k -> Map k a -> Bool
member = k -> Map k a -> Bool
forall {t} {a}. Ord t => t -> Map t a -> Bool
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: t -> Map t a -> Bool
go !t
_ Map t a
Tip = Bool
False
go t
k (Bin Int
_ t
kx a
_ Map t a
l Map t a
r) = case t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord t
compare t
k t
kx of
Ordering
LT -> t -> Map t a -> Bool
go t
k Map t a
l
Ordering
GT -> t -> Map t a -> Bool
go t
k Map t a
r
Ordering
EQ -> Bool
True
#if __GLASGOW_HASKELL__
{-# INLINABLE member #-}
#else
{-# INLINE member #-}
#endif
notMember :: Ord k => k -> Map k a -> Bool
notMember :: k -> Map k a -> Bool
notMember k
k Map k a
m = Bool -> Bool
not (Bool -> Bool) -> Bool -> Bool
forall a b. (a -> b) -> a -> b
$ k -> Map k a -> Bool
forall {t} {a}. Ord t => t -> Map t a -> Bool
Evidence bound by a type signature of the constraint type Ord k
member k
k Map k a
m
#if __GLASGOW_HASKELL__
{-# INLINABLE notMember #-}
#else
{-# INLINE notMember #-}
#endif
find :: Ord k => k -> Map k a -> a
find :: k -> Map k a -> a
find = k -> Map k a -> a
forall k a. Ord k => k -> Map k a -> a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: t -> Map t p -> p
go !t
_ Map t p
Tip = [Char] -> p
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.!: given key is not an element in the map"
go t
k (Bin Int
_ t
kx p
x Map t p
l Map t p
r) = case t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord t
compare t
k t
kx of
Ordering
LT -> t -> Map t p -> p
go t
k Map t p
l
Ordering
GT -> t -> Map t p -> p
go t
k Map t p
r
Ordering
EQ -> p
x
#if __GLASGOW_HASKELL__
{-# INLINABLE find #-}
#else
{-# INLINE find #-}
#endif
findWithDefault :: Ord k => a -> k -> Map k a -> a
findWithDefault :: a -> k -> Map k a -> a
findWithDefault = a -> k -> Map k a -> a
forall {t} {t}. Ord t => t -> t -> Map t t -> t
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: t -> t -> Map t t -> t
go t
def !t
_ Map t t
Tip = t
def
go t
def t
k (Bin Int
_ t
kx t
x Map t t
l Map t t
r) = case t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord t
compare t
k t
kx of
Ordering
LT -> t -> t -> Map t t -> t
go t
def t
k Map t t
l
Ordering
GT -> t -> t -> Map t t -> t
go t
def t
k Map t t
r
Ordering
EQ -> t
x
#if __GLASGOW_HASKELL__
{-# INLINABLE findWithDefault #-}
#else
{-# INLINE findWithDefault #-}
#endif
lookupLT :: Ord k => k -> Map k v -> Maybe (k, v)
lookupLT :: k -> Map k v -> Maybe (k, v)
lookupLT = k -> Map k v -> Maybe (k, v)
forall {t} {t}. Ord t => t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord k
goNothing
where
goNothing :: t -> Map t t -> Maybe (t, t)
goNothing !t
_ Map t t
Tip = Maybe (t, t)
forall a. Maybe a
Nothing
goNothing t
k (Bin Int
_ t
kx t
x Map t t
l Map t t
r) | t
k t -> t -> Bool
forall a. Ord a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Ord t
<= t
kx = t -> Map t t -> Maybe (t, t)
goNothing t
k Map t t
l
| Bool
otherwise = t -> t -> t -> Map t t -> Maybe (t, t)
forall {t} {t}. Ord t => t -> t -> t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord t
goJust t
k t
kx t
x Map t t
r
goJust :: t -> t -> t -> Map t t -> Maybe (t, t)
goJust !t
_ t
kx' t
x' Map t t
Tip = (t, t) -> Maybe (t, t)
forall a. a -> Maybe a
Just (t
kx', t
x')
goJust t
k t
kx' t
x' (Bin Int
_ t
kx t
x Map t t
l Map t t
r) | t
k t -> t -> Bool
forall a. Ord a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Ord t
<= t
kx = t -> t -> t -> Map t t -> Maybe (t, t)
goJust t
k t
kx' t
x' Map t t
l
| Bool
otherwise = t -> t -> t -> Map t t -> Maybe (t, t)
goJust t
k t
kx t
x Map t t
r
#if __GLASGOW_HASKELL__
{-# INLINABLE lookupLT #-}
#else
{-# INLINE lookupLT #-}
#endif
lookupGT :: Ord k => k -> Map k v -> Maybe (k, v)
lookupGT :: k -> Map k v -> Maybe (k, v)
lookupGT = k -> Map k v -> Maybe (k, v)
forall {t} {t}. Ord t => t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord k
goNothing
where
goNothing :: t -> Map t t -> Maybe (t, t)
goNothing !t
_ Map t t
Tip = Maybe (t, t)
forall a. Maybe a
Nothing
goNothing t
k (Bin Int
_ t
kx t
x Map t t
l Map t t
r) | t
k t -> t -> Bool
forall a. Ord a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Ord t
< t
kx = t -> t -> t -> Map t t -> Maybe (t, t)
forall {t} {t}. Ord t => t -> t -> t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord t
goJust t
k t
kx t
x Map t t
l
| Bool
otherwise = t -> Map t t -> Maybe (t, t)
goNothing t
k Map t t
r
goJust :: t -> t -> t -> Map t t -> Maybe (t, t)
goJust !t
_ t
kx' t
x' Map t t
Tip = (t, t) -> Maybe (t, t)
forall a. a -> Maybe a
Just (t
kx', t
x')
goJust t
k t
kx' t
x' (Bin Int
_ t
kx t
x Map t t
l Map t t
r) | t
k t -> t -> Bool
forall a. Ord a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Ord t
< t
kx = t -> t -> t -> Map t t -> Maybe (t, t)
goJust t
k t
kx t
x Map t t
l
| Bool
otherwise = t -> t -> t -> Map t t -> Maybe (t, t)
goJust t
k t
kx' t
x' Map t t
r
#if __GLASGOW_HASKELL__
{-# INLINABLE lookupGT #-}
#else
{-# INLINE lookupGT #-}
#endif
lookupLE :: Ord k => k -> Map k v -> Maybe (k, v)
lookupLE :: k -> Map k v -> Maybe (k, v)
lookupLE = k -> Map k v -> Maybe (k, v)
forall {t} {t}. Ord t => t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord k
goNothing
where
goNothing :: t -> Map t t -> Maybe (t, t)
goNothing !t
_ Map t t
Tip = Maybe (t, t)
forall a. Maybe a
Nothing
goNothing t
k (Bin Int
_ t
kx t
x Map t t
l Map t t
r) = case t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord t
compare t
k t
kx of Ordering
LT -> t -> Map t t -> Maybe (t, t)
goNothing t
k Map t t
l
Ordering
EQ -> (t, t) -> Maybe (t, t)
forall a. a -> Maybe a
Just (t
kx, t
x)
Ordering
GT -> t -> t -> t -> Map t t -> Maybe (t, t)
forall {t} {t}. Ord t => t -> t -> t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord t
goJust t
k t
kx t
x Map t t
r
goJust :: t -> t -> t -> Map t t -> Maybe (t, t)
goJust !t
_ t
kx' t
x' Map t t
Tip = (t, t) -> Maybe (t, t)
forall a. a -> Maybe a
Just (t
kx', t
x')
goJust t
k t
kx' t
x' (Bin Int
_ t
kx t
x Map t t
l Map t t
r) = case t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord t
compare t
k t
kx of Ordering
LT -> t -> t -> t -> Map t t -> Maybe (t, t)
goJust t
k t
kx' t
x' Map t t
l
Ordering
EQ -> (t, t) -> Maybe (t, t)
forall a. a -> Maybe a
Just (t
kx, t
x)
Ordering
GT -> t -> t -> t -> Map t t -> Maybe (t, t)
goJust t
k t
kx t
x Map t t
r
#if __GLASGOW_HASKELL__
{-# INLINABLE lookupLE #-}
#else
{-# INLINE lookupLE #-}
#endif
lookupGE :: Ord k => k -> Map k v -> Maybe (k, v)
lookupGE :: k -> Map k v -> Maybe (k, v)
lookupGE = k -> Map k v -> Maybe (k, v)
forall {t} {t}. Ord t => t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord k
goNothing
where
goNothing :: t -> Map t b -> Maybe (t, b)
goNothing !t
_ Map t b
Tip = Maybe (t, b)
forall a. Maybe a
Nothing
goNothing t
k (Bin Int
_ t
kx b
x Map t b
l Map t b
r) = case t -> t -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord t
compare t
k t
kx of Ordering
LT -> t -> t -> b -> Map t b -> Maybe (t, b)
forall {t} {t}. Ord t => t -> t -> t -> Map t t -> Maybe (t, t)
Evidence bound by a type signature of the constraint type Ord t
goJust t
k t
kx b
x Map t b
l
Ordering
EQ -> (t, b) -> Maybe (t, b)
forall a. a -> Maybe a
Just (t
kx, b
x)
Ordering
GT -> t -> Map t b -> Maybe (t, b)
goNothing t
k Map t b
r
goJust :: a -> a -> b -> Map a b -> Maybe (a, b)
goJust !a
_ a
kx' b
x' Map a b
Tip = (a, b) -> Maybe (a, b)
forall a. a -> Maybe a
Just (a
kx', b
x')
goJust a
k a
kx' b
x' (Bin Int
_ a
kx b
x Map a b
l Map a b
r) = case a -> a -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord a
compare a
k a
kx of Ordering
LT -> a -> a -> b -> Map a b -> Maybe (a, b)
goJust a
k a
kx b
x Map a b
l
Ordering
EQ -> (a, b) -> Maybe (a, b)
forall a. a -> Maybe a
Just (a
kx, b
x)
Ordering
GT -> a -> a -> b -> Map a b -> Maybe (a, b)
goJust a
k a
kx' b
x' Map a b
r
#if __GLASGOW_HASKELL__
{-# INLINABLE lookupGE #-}
#else
{-# INLINE lookupGE #-}
#endif
empty :: Map k a
empty :: Map k a
empty = Map k a
forall k a. Map k a
Tip
{-# INLINE empty #-}
singleton :: k -> a -> Map k a
singleton :: k -> a -> Map k a
singleton k
k a
x = Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip
{-# INLINE singleton #-}
insert :: Ord k => k -> a -> Map k a -> Map k a
insert :: k -> a -> Map k a -> Map k a
insert k
kx0 = k -> k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
kx0 k
kx0
where
go :: Ord k => k -> k -> a -> Map k a -> Map k a
go :: k -> k -> a -> Map k a -> Map k a
go k
orig !k
_ a
x Map k a
Tip = k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton (k -> k
forall a. a -> a
lazy k
orig) a
x
go k
orig !k
kx a
x t :: Map k a
t@(Bin Int
sz k
ky a
y Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
kx k
ky of
Ordering
LT | Map k a
l' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l -> Map k a
t
| Bool
otherwise -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y Map k a
l' Map k a
r
where !l' :: Map k a
l' = k -> k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
orig k
kx a
x Map k a
l
Ordering
GT | Map k a
r' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r -> Map k a
t
| Bool
otherwise -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l Map k a
r'
where !r' :: Map k a
r' = k -> k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
orig k
kx a
x Map k a
r
Ordering
EQ | a
x a -> a -> Bool
forall a. a -> a -> Bool
`ptrEq` a
y Bool -> Bool -> Bool
&& (k -> k
forall a. a -> a
lazy k
orig k -> Bool -> Bool
`seq` (k
orig k -> k -> Bool
forall a. a -> a -> Bool
`ptrEq` k
ky)) -> Map k a
t
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sz (k -> k
forall a. a -> a
lazy k
orig) a
x Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE insert #-}
#else
{-# INLINE insert #-}
#endif
#ifndef __GLASGOW_HASKELL__
lazy :: a -> a
lazy a = a
#endif
insertR :: Ord k => k -> a -> Map k a -> Map k a
insertR :: k -> a -> Map k a -> Map k a
insertR k
kx0 = k -> k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
kx0 k
kx0
where
go :: Ord k => k -> k -> a -> Map k a -> Map k a
go :: k -> k -> a -> Map k a -> Map k a
go k
orig !k
_ a
x Map k a
Tip = k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton (k -> k
forall a. a -> a
lazy k
orig) a
x
go k
orig !k
kx a
x t :: Map k a
t@(Bin Int
_ k
ky a
y Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
kx k
ky of
Ordering
LT | Map k a
l' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l -> Map k a
t
| Bool
otherwise -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y Map k a
l' Map k a
r
where !l' :: Map k a
l' = k -> k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
orig k
kx a
x Map k a
l
Ordering
GT | Map k a
r' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r -> Map k a
t
| Bool
otherwise -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l Map k a
r'
where !r' :: Map k a
r' = k -> k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
orig k
kx a
x Map k a
r
Ordering
EQ -> Map k a
t
#if __GLASGOW_HASKELL__
{-# INLINABLE insertR #-}
#else
{-# INLINE insertR #-}
#endif
insertWith :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWith :: (a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWith = (a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
go :: (a -> a -> a) -> k -> a -> Map k a -> Map k a
go a -> a -> a
_ !k
kx a
x Map k a
Tip = k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x
go a -> a -> a
f !k
kx a
x (Bin Int
sy k
ky a
y Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
kx k
ky of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y ((a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go a -> a -> a
f k
kx a
x Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l ((a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go a -> a -> a
f k
kx a
x Map k a
r)
Ordering
EQ -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sy k
kx (a -> a -> a
f a
x a
y) Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE insertWith #-}
#else
{-# INLINE insertWith #-}
#endif
insertWithR :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithR :: (a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithR = (a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
go :: (a -> a -> a) -> k -> a -> Map k a -> Map k a
go a -> a -> a
_ !k
kx a
x Map k a
Tip = k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x
go a -> a -> a
f !k
kx a
x (Bin Int
sy k
ky a
y Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
kx k
ky of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y ((a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go a -> a -> a
f k
kx a
x Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l ((a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go a -> a -> a
f k
kx a
x Map k a
r)
Ordering
EQ -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sy k
ky (a -> a -> a
f a
y a
x) Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE insertWithR #-}
#else
{-# INLINE insertWithR #-}
#endif
insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithKey :: (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithKey = (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
go :: (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
go k -> a -> a -> a
_ !k
kx a
x Map k a
Tip = k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x
go k -> a -> a -> a
f k
kx a
x (Bin Int
sy k
ky a
y Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
kx k
ky of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y ((k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a -> a
f k
kx a
x Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l ((k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a -> a
f k
kx a
x Map k a
r)
Ordering
EQ -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sy k
kx (k -> a -> a -> a
f k
kx a
x a
y) Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE insertWithKey #-}
#else
{-# INLINE insertWithKey #-}
#endif
insertWithKeyR :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithKeyR :: (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithKeyR = (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
go :: (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
go k -> a -> a -> a
_ !k
kx a
x Map k a
Tip = k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x
go k -> a -> a -> a
f k
kx a
x (Bin Int
sy k
ky a
y Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
kx k
ky of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y ((k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a -> a
f k
kx a
x Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l ((k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a -> a
f k
kx a
x Map k a
r)
Ordering
EQ -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sy k
ky (k -> a -> a -> a
f k
ky a
y a
x) Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE insertWithKeyR #-}
#else
{-# INLINE insertWithKeyR #-}
#endif
insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a
-> (Maybe a, Map k a)
insertLookupWithKey :: (k -> a -> a -> a) -> k -> a -> Map k a -> (Maybe a, Map k a)
insertLookupWithKey k -> a -> a -> a
f0 k
k0 a
x0 = StrictPair (Maybe a) (Map k a) -> (Maybe a, Map k a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Maybe a) (Map k a) -> (Maybe a, Map k a))
-> (Map k a -> StrictPair (Maybe a) (Map k a))
-> Map k a
-> (Maybe a, Map k a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k -> a -> a -> a)
-> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall k a.
Ord k =>
(k -> a -> a -> a)
-> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a -> a
f0 k
k0 a
x0
where
go :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
go :: (k -> a -> a -> a)
-> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
go k -> a -> a -> a
_ !k
kx a
x Map k a
Tip = (Maybe a
forall a. Maybe a
Nothing Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x)
go k -> a -> a -> a
f k
kx a
x (Bin Int
sy k
ky a
y Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
kx k
ky of
Ordering
LT -> let !(Maybe a
found :*: Map k a
l') = (k -> a -> a -> a)
-> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall k a.
Ord k =>
(k -> a -> a -> a)
-> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a -> a
f k
kx a
x Map k a
l
!t' :: Map k a
t' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y Map k a
l' Map k a
r
in (Maybe a
found Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
t')
Ordering
GT -> let !(Maybe a
found :*: Map k a
r') = (k -> a -> a -> a)
-> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall k a.
Ord k =>
(k -> a -> a -> a)
-> k -> a -> Map k a -> StrictPair (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a -> a
f k
kx a
x Map k a
r
!t' :: Map k a
t' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l Map k a
r'
in (Maybe a
found Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
t')
Ordering
EQ -> (a -> Maybe a
forall a. a -> Maybe a
Just a
y Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sy k
kx (k -> a -> a -> a
f k
kx a
x a
y) Map k a
l Map k a
r)
#if __GLASGOW_HASKELL__
{-# INLINABLE insertLookupWithKey #-}
#else
{-# INLINE insertLookupWithKey #-}
#endif
delete :: Ord k => k -> Map k a -> Map k a
delete :: k -> Map k a -> Map k a
delete = k -> Map k a -> Map k a
forall k a. Ord k => k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => k -> Map k a -> Map k a
go :: k -> Map k a -> Map k a
go !k
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
go k
k t :: Map k a
t@(Bin Int
_ k
kx a
x Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT | Map k a
l' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l -> Map k a
t
| Bool
otherwise -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x Map k a
l' Map k a
r
where !l' :: Map k a
l' = k -> Map k a -> Map k a
forall k a. Ord k => k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
k Map k a
l
Ordering
GT | Map k a
r' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r -> Map k a
t
| Bool
otherwise -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l Map k a
r'
where !r' :: Map k a
r' = k -> Map k a -> Map k a
forall k a. Ord k => k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k
k Map k a
r
Ordering
EQ -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE delete #-}
#else
{-# INLINE delete #-}
#endif
adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a
adjust :: (a -> a) -> k -> Map k a -> Map k a
adjust a -> a
f = (k -> a -> a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
adjustWithKey (\k
_ a
x -> a -> a
f a
x)
#if __GLASGOW_HASKELL__
{-# INLINABLE adjust #-}
#else
{-# INLINE adjust #-}
#endif
adjustWithKey :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k a
adjustWithKey :: (k -> a -> a) -> k -> Map k a -> Map k a
adjustWithKey = (k -> a -> a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => (k -> a -> a) -> k -> Map k a -> Map k a
go :: (k -> a -> a) -> k -> Map k a -> Map k a
go k -> a -> a
_ !k
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
go k -> a -> a
f k
k (Bin Int
sx k
kx a
x Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x ((k -> a -> a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a
f k
k Map k a
l) Map k a
r
Ordering
GT -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x Map k a
l ((k -> a -> a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> a
f k
k Map k a
r)
Ordering
EQ -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx (k -> a -> a
f k
kx a
x) Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE adjustWithKey #-}
#else
{-# INLINE adjustWithKey #-}
#endif
update :: Ord k => (a -> Maybe a) -> k -> Map k a -> Map k a
update :: (a -> Maybe a) -> k -> Map k a -> Map k a
update a -> Maybe a
f = (k -> a -> Maybe a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
updateWithKey (\k
_ a
x -> a -> Maybe a
f a
x)
#if __GLASGOW_HASKELL__
{-# INLINABLE update #-}
#else
{-# INLINE update #-}
#endif
updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
updateWithKey :: (k -> a -> Maybe a) -> k -> Map k a -> Map k a
updateWithKey = (k -> a -> Maybe a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
go :: (k -> a -> Maybe a) -> k -> Map k a -> Map k a
go k -> a -> Maybe a
_ !k
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
go k -> a -> Maybe a
f k
k(Bin Int
sx k
kx a
x Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x ((k -> a -> Maybe a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> Maybe a
f k
k Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l ((k -> a -> Maybe a) -> k -> Map k a -> Map k a
forall k a. Ord k => (k -> a -> Maybe a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> Maybe a
f k
k Map k a
r)
Ordering
EQ -> case k -> a -> Maybe a
f k
kx a
x of
Just a
x' -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
l Map k a
r
Maybe a
Nothing -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE updateWithKey #-}
#else
{-# INLINE updateWithKey #-}
#endif
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a,Map k a)
updateLookupWithKey :: (k -> a -> Maybe a) -> k -> Map k a -> (Maybe a, Map k a)
updateLookupWithKey k -> a -> Maybe a
f0 k
k0 = StrictPair (Maybe a) (Map k a) -> (Maybe a, Map k a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Maybe a) (Map k a) -> (Maybe a, Map k a))
-> (Map k a -> StrictPair (Maybe a) (Map k a))
-> Map k a
-> (Maybe a, Map k a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k -> a -> Maybe a)
-> k -> Map k a -> StrictPair (Maybe a) (Map k a)
forall k a.
Ord k =>
(k -> a -> Maybe a)
-> k -> Map k a -> StrictPair (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> Maybe a
f0 k
k0
where
go :: Ord k => (k -> a -> Maybe a) -> k -> Map k a -> StrictPair (Maybe a) (Map k a)
go :: (k -> a -> Maybe a)
-> k -> Map k a -> StrictPair (Maybe a) (Map k a)
go k -> a -> Maybe a
_ !k
_ Map k a
Tip = (Maybe a
forall a. Maybe a
Nothing Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
forall k a. Map k a
Tip)
go k -> a -> Maybe a
f k
k (Bin Int
sx k
kx a
x Map k a
l Map k a
r) =
case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> let !(Maybe a
found :*: Map k a
l') = (k -> a -> Maybe a)
-> k -> Map k a -> StrictPair (Maybe a) (Map k a)
forall k a.
Ord k =>
(k -> a -> Maybe a)
-> k -> Map k a -> StrictPair (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> Maybe a
f k
k Map k a
l
!t' :: Map k a
t' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x Map k a
l' Map k a
r
in (Maybe a
found Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
t')
Ordering
GT -> let !(Maybe a
found :*: Map k a
r') = (k -> a -> Maybe a)
-> k -> Map k a -> StrictPair (Maybe a) (Map k a)
forall k a.
Ord k =>
(k -> a -> Maybe a)
-> k -> Map k a -> StrictPair (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k -> a -> Maybe a
f k
k Map k a
r
!t' :: Map k a
t' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l Map k a
r'
in (Maybe a
found Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
t')
Ordering
EQ -> case k -> a -> Maybe a
f k
kx a
x of
Just a
x' -> (a -> Maybe a
forall a. a -> Maybe a
Just a
x' Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
l Map k a
r)
Maybe a
Nothing -> let !glued :: Map k a
glued = Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
in (a -> Maybe a
forall a. a -> Maybe a
Just a
x Maybe a -> Map k a -> StrictPair (Maybe a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
glued)
#if __GLASGOW_HASKELL__
{-# INLINABLE updateLookupWithKey #-}
#else
{-# INLINE updateLookupWithKey #-}
#endif
alter :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a
alter :: (Maybe a -> Maybe a) -> k -> Map k a -> Map k a
alter = (Maybe a -> Maybe a) -> k -> Map k a -> Map k a
forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go
where
go :: Ord k => (Maybe a -> Maybe a) -> k -> Map k a -> Map k a
go :: (Maybe a -> Maybe a) -> k -> Map k a -> Map k a
go Maybe a -> Maybe a
f !k
k Map k a
Tip = case Maybe a -> Maybe a
f Maybe a
forall a. Maybe a
Nothing of
Maybe a
Nothing -> Map k a
forall k a. Map k a
Tip
Just a
x -> k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
k a
x
go Maybe a -> Maybe a
f k
k (Bin Int
sx k
kx a
x Map k a
l Map k a
r) = case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balance k
kx a
x ((Maybe a -> Maybe a) -> k -> Map k a -> Map k a
forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go Maybe a -> Maybe a
f k
k Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balance k
kx a
x Map k a
l ((Maybe a -> Maybe a) -> k -> Map k a -> Map k a
forall k a.
Ord k =>
(Maybe a -> Maybe a) -> k -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
go Maybe a -> Maybe a
f k
k Map k a
r)
Ordering
EQ -> case Maybe a -> Maybe a
f (a -> Maybe a
forall a. a -> Maybe a
Just a
x) of
Just a
x' -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
l Map k a
r
Maybe a
Nothing -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE alter #-}
#else
{-# INLINE alter #-}
#endif
data AreWeStrict = Strict | Lazy
alterF :: (Functor f, Ord k)
=> (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a)
alterF :: (Maybe a -> f (Maybe a)) -> k -> Map k a -> f (Map k a)
alterF Maybe a -> f (Maybe a)
f k
k Map k a
m = AreWeStrict
-> k -> (Maybe a -> f (Maybe a)) -> Map k a -> f (Map k a)
forall (f :: * -> *) k a.
(Functor f, Ord k) =>
AreWeStrict
-> k -> (Maybe a -> f (Maybe a)) -> Map k a -> f (Map k a)
Evidence bound by a type signature of the constraint type Ord k
Evidence bound by a type signature of the constraint type Functor f
atKeyImpl AreWeStrict
Lazy k
k Maybe a -> f (Maybe a)
f Map k a
m
#ifndef __GLASGOW_HASKELL__
{-# INLINE alterF #-}
#else
{-# INLINABLE [2] alterF #-}
{-# RULES
"alterF/Const" forall k (f :: Maybe a -> Const b (Maybe a)) . alterF f k = \m -> Const . getConst . f $ lookup k m
#-}
#if MIN_VERSION_base(4,8,0)
{-# RULES
"alterF/Identity" forall k f . alterF f k = atKeyIdentity k f
#-}
#endif
#endif
atKeyImpl :: (Functor f, Ord k) =>
AreWeStrict -> k -> (Maybe a -> f (Maybe a)) -> Map k a -> f (Map k a)
#ifdef DEFINE_ALTERF_FALLBACK
atKeyImpl strict !k f m
| wordSize < 61 && size m >= alterFCutoff = alterFFallback strict k f m
#endif
atKeyImpl :: AreWeStrict
-> k -> (Maybe a -> f (Maybe a)) -> Map k a -> f (Map k a)
atKeyImpl AreWeStrict
strict !k
k Maybe a -> f (Maybe a)
f Map k a
m = case k -> Map k a -> TraceResult a
forall k a. Ord k => k -> Map k a -> TraceResult a
Evidence bound by a type signature of the constraint type Ord k
lookupTrace k
k Map k a
m of
TraceResult Maybe a
mv BitQueue
q -> ((Maybe a -> Map k a) -> f (Maybe a) -> f (Map k a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
<$> Maybe a -> f (Maybe a)
f Maybe a
mv) ((Maybe a -> Map k a) -> f (Map k a))
-> (Maybe a -> Map k a) -> f (Map k a)
forall a b. (a -> b) -> a -> b
$ \ Maybe a
fres ->
case Maybe a
fres of
Maybe a
Nothing -> case Maybe a
mv of
Maybe a
Nothing -> Map k a
m
Just a
old -> a -> BitQueue -> Map k a -> Map k a
forall any k a. any -> BitQueue -> Map k a -> Map k a
deleteAlong a
old BitQueue
q Map k a
m
Just a
new -> case AreWeStrict
strict of
AreWeStrict
Strict -> a
new a -> Map k a -> Map k a
`seq` case Maybe a
mv of
Maybe a
Nothing -> BitQueue -> k -> a -> Map k a -> Map k a
forall k a. BitQueue -> k -> a -> Map k a -> Map k a
insertAlong BitQueue
q k
k a
new Map k a
m
Just a
_ -> BitQueue -> a -> Map k a -> Map k a
forall a k. BitQueue -> a -> Map k a -> Map k a
replaceAlong BitQueue
q a
new Map k a
m
AreWeStrict
Lazy -> case Maybe a
mv of
Maybe a
Nothing -> BitQueue -> k -> a -> Map k a -> Map k a
forall k a. BitQueue -> k -> a -> Map k a -> Map k a
insertAlong BitQueue
q k
k a
new Map k a
m
Just a
_ -> BitQueue -> a -> Map k a -> Map k a
forall a k. BitQueue -> a -> Map k a -> Map k a
replaceAlong BitQueue
q a
new Map k a
m
{-# INLINE atKeyImpl #-}
#ifdef DEFINE_ALTERF_FALLBACK
alterFCutoff :: Int
#if WORD_SIZE_IN_BITS == 32
alterFCutoff = 55744454
#else
alterFCutoff = case wordSize of
30 -> 17637893
31 -> 31356255
32 -> 55744454
x -> (4^(x*2-2)) `quot` (3^(x*2-2))
#endif
#endif
data TraceResult a = TraceResult (Maybe a) {-# UNPACK #-} !BitQueue
lookupTrace :: Ord k => k -> Map k a -> TraceResult a
lookupTrace :: k -> Map k a -> TraceResult a
lookupTrace = BitQueueB -> k -> Map k a -> TraceResult a
forall k a. Ord k => BitQueueB -> k -> Map k a -> TraceResult a
Evidence bound by a type signature of the constraint type Ord k
go BitQueueB
emptyQB
where
go :: Ord k => BitQueueB -> k -> Map k a -> TraceResult a
go :: BitQueueB -> k -> Map k a -> TraceResult a
go !BitQueueB
q !k
_ Map k a
Tip = Maybe a -> BitQueue -> TraceResult a
forall a. Maybe a -> BitQueue -> TraceResult a
TraceResult Maybe a
forall a. Maybe a
Nothing (BitQueueB -> BitQueue
buildQ BitQueueB
q)
go BitQueueB
q k
k (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> (BitQueueB -> k -> Map k a -> TraceResult a
forall k a. Ord k => BitQueueB -> k -> Map k a -> TraceResult a
Evidence bound by a type signature of the constraint type Ord k
go (BitQueueB -> k -> Map k a -> TraceResult a)
-> BitQueueB -> k -> Map k a -> TraceResult a
forall a b. (a -> b) -> a -> b
$! BitQueueB
q BitQueueB -> Bool -> BitQueueB
`snocQB` Bool
False) k
k Map k a
l
Ordering
GT -> (BitQueueB -> k -> Map k a -> TraceResult a
forall k a. Ord k => BitQueueB -> k -> Map k a -> TraceResult a
Evidence bound by a type signature of the constraint type Ord k
go (BitQueueB -> k -> Map k a -> TraceResult a)
-> BitQueueB -> k -> Map k a -> TraceResult a
forall a b. (a -> b) -> a -> b
$! BitQueueB
q BitQueueB -> Bool -> BitQueueB
`snocQB` Bool
True) k
k Map k a
r
Ordering
EQ -> Maybe a -> BitQueue -> TraceResult a
forall a. Maybe a -> BitQueue -> TraceResult a
TraceResult (a -> Maybe a
forall a. a -> Maybe a
Just a
x) (BitQueueB -> BitQueue
buildQ BitQueueB
q)
#if __GLASGOW_HASKELL__ >= 710
{-# INLINABLE lookupTrace #-}
#else
{-# INLINE lookupTrace #-}
#endif
insertAlong :: BitQueue -> k -> a -> Map k a -> Map k a
insertAlong :: BitQueue -> k -> a -> Map k a -> Map k a
insertAlong !BitQueue
_ k
kx a
x Map k a
Tip = k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x
insertAlong BitQueue
q k
kx a
x (Bin Int
sz k
ky a
y Map k a
l Map k a
r) =
case BitQueue -> Maybe (Bool, BitQueue)
unconsQ BitQueue
q of
Just (Bool
False, BitQueue
tl) -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y (BitQueue -> k -> a -> Map k a -> Map k a
forall k a. BitQueue -> k -> a -> Map k a -> Map k a
insertAlong BitQueue
tl k
kx a
x Map k a
l) Map k a
r
Just (Bool
True,BitQueue
tl) -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l (BitQueue -> k -> a -> Map k a -> Map k a
forall k a. BitQueue -> k -> a -> Map k a -> Map k a
insertAlong BitQueue
tl k
kx a
x Map k a
r)
Maybe (Bool, BitQueue)
Nothing -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sz k
kx a
x Map k a
l Map k a
r
deleteAlong :: any -> BitQueue -> Map k a -> Map k a
deleteAlong :: any -> BitQueue -> Map k a -> Map k a
deleteAlong any
old !BitQueue
q0 !Map k a
m = Proxy# () -> BitQueue -> Map k a -> Map k a
forall k a. Proxy# () -> BitQueue -> Map k a -> Map k a
go (any -> Proxy# ()
forall a. a -> Proxy# ()
bogus any
old) BitQueue
q0 Map k a
m where
#ifdef USE_MAGIC_PROXY
go :: Proxy# () -> BitQueue -> Map k a -> Map k a
#else
go :: any -> BitQueue -> Map k a -> Map k a
#endif
go :: Proxy# () -> BitQueue -> Map k a -> Map k a
go !Proxy# ()
_ !BitQueue
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
go Proxy# ()
foom BitQueue
q (Bin Int
_ k
ky a
y Map k a
l Map k a
r) =
case BitQueue -> Maybe (Bool, BitQueue)
unconsQ BitQueue
q of
Just (Bool
False, BitQueue
tl) -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y (Proxy# () -> BitQueue -> Map k a -> Map k a
forall k a. Proxy# () -> BitQueue -> Map k a -> Map k a
go Proxy# ()
foom BitQueue
tl Map k a
l) Map k a
r
Just (Bool
True, BitQueue
tl) -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y Map k a
l (Proxy# () -> BitQueue -> Map k a -> Map k a
forall k a. Proxy# () -> BitQueue -> Map k a -> Map k a
go Proxy# ()
foom BitQueue
tl Map k a
r)
Maybe (Bool, BitQueue)
Nothing -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
#ifdef USE_MAGIC_PROXY
{-# NOINLINE bogus #-}
bogus :: a -> Proxy# ()
bogus :: a -> Proxy# ()
bogus a
_ = Proxy# ()
forall {k} (a :: k). Proxy# a
proxy#
#else
{-# INLINE bogus #-}
bogus :: a -> a
bogus a = a
#endif
replaceAlong :: BitQueue -> a -> Map k a -> Map k a
replaceAlong :: BitQueue -> a -> Map k a -> Map k a
replaceAlong !BitQueue
_ a
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
replaceAlong BitQueue
q a
x (Bin Int
sz k
ky a
y Map k a
l Map k a
r) =
case BitQueue -> Maybe (Bool, BitQueue)
unconsQ BitQueue
q of
Just (Bool
False, BitQueue
tl) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sz k
ky a
y (BitQueue -> a -> Map k a -> Map k a
forall a k. BitQueue -> a -> Map k a -> Map k a
replaceAlong BitQueue
tl a
x Map k a
l) Map k a
r
Just (Bool
True,BitQueue
tl) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sz k
ky a
y Map k a
l (BitQueue -> a -> Map k a -> Map k a
forall a k. BitQueue -> a -> Map k a -> Map k a
replaceAlong BitQueue
tl a
x Map k a
r)
Maybe (Bool, BitQueue)
Nothing -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sz k
ky a
x Map k a
l Map k a
r
#if __GLASGOW_HASKELL__ && MIN_VERSION_base(4,8,0)
atKeyIdentity :: Ord k => k -> (Maybe a -> Identity (Maybe a)) -> Map k a -> Identity (Map k a)
atKeyIdentity :: k
-> (Maybe a -> Identity (Maybe a)) -> Map k a -> Identity (Map k a)
atKeyIdentity k
k Maybe a -> Identity (Maybe a)
f Map k a
t = Map k a -> Identity (Map k a)
forall a. a -> Identity a
Identity (Map k a -> Identity (Map k a)) -> Map k a -> Identity (Map k a)
forall a b. (a -> b) -> a -> b
$ AreWeStrict -> k -> (Maybe a -> Maybe a) -> Map k a -> Map k a
forall k a.
Ord k =>
AreWeStrict -> k -> (Maybe a -> Maybe a) -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
atKeyPlain AreWeStrict
Lazy k
k ((Maybe a -> Identity (Maybe a)) -> Maybe a -> Maybe a
coerce Maybe a -> Identity (Maybe a)
f) Map k a
t
{-# INLINABLE atKeyIdentity #-}
atKeyPlain :: Ord k => AreWeStrict -> k -> (Maybe a -> Maybe a) -> Map k a -> Map k a
atKeyPlain :: AreWeStrict -> k -> (Maybe a -> Maybe a) -> Map k a -> Map k a
atKeyPlain AreWeStrict
strict k
k0 Maybe a -> Maybe a
f0 Map k a
t = case k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
forall k a.
Ord k =>
k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
Evidence bound by a type signature of the constraint type Ord k
go k
k0 Maybe a -> Maybe a
f0 Map k a
t of
AltSmaller Map k a
t' -> Map k a
t'
AltBigger Map k a
t' -> Map k a
t'
AltAdj Map k a
t' -> Map k a
t'
Altered k a
AltSame -> Map k a
t
where
go :: Ord k => k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
go :: k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
go !k
k Maybe a -> Maybe a
f Map k a
Tip = case Maybe a -> Maybe a
f Maybe a
forall a. Maybe a
Nothing of
Maybe a
Nothing -> Altered k a
forall k a. Altered k a
AltSame
Just a
x -> case AreWeStrict
strict of
AreWeStrict
Lazy -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltBigger (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
k a
x
AreWeStrict
Strict -> a
x a -> Altered k a -> Altered k a
`seq` (Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltBigger (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
k a
x)
go k
k Maybe a -> Maybe a
f (Bin Int
sx k
kx a
x Map k a
l Map k a
r) = case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> case k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
forall k a.
Ord k =>
k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
Evidence bound by a type signature of the constraint type Ord k
go k
k Maybe a -> Maybe a
f Map k a
l of
AltSmaller Map k a
l' -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltSmaller (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x Map k a
l' Map k a
r
AltBigger Map k a
l' -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltBigger (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l' Map k a
r
AltAdj Map k a
l' -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltAdj (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x Map k a
l' Map k a
r
Altered k a
AltSame -> Altered k a
forall k a. Altered k a
AltSame
Ordering
GT -> case k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
forall k a.
Ord k =>
k -> (Maybe a -> Maybe a) -> Map k a -> Altered k a
Evidence bound by a type signature of the constraint type Ord k
go k
k Maybe a -> Maybe a
f Map k a
r of
AltSmaller Map k a
r' -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltSmaller (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l Map k a
r'
AltBigger Map k a
r' -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltBigger (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x Map k a
l Map k a
r'
AltAdj Map k a
r' -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltAdj (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x Map k a
l Map k a
r'
Altered k a
AltSame -> Altered k a
forall k a. Altered k a
AltSame
Ordering
EQ -> case Maybe a -> Maybe a
f (a -> Maybe a
forall a. a -> Maybe a
Just a
x) of
Just a
x' -> case AreWeStrict
strict of
AreWeStrict
Lazy -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltAdj (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
l Map k a
r
AreWeStrict
Strict -> a
x' a -> Altered k a -> Altered k a
`seq` (Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltAdj (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
l Map k a
r)
Maybe a
Nothing -> Map k a -> Altered k a
forall k a. Map k a -> Altered k a
AltSmaller (Map k a -> Altered k a) -> Map k a -> Altered k a
forall a b. (a -> b) -> a -> b
$ Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
{-# INLINE atKeyPlain #-}
data Altered k a = AltSmaller !(Map k a) | AltBigger !(Map k a) | AltAdj !(Map k a) | AltSame
#endif
#ifdef DEFINE_ALTERF_FALLBACK
alterFFallback :: (Functor f, Ord k)
=> AreWeStrict -> k -> (Maybe a -> f (Maybe a)) -> Map k a -> f (Map k a)
alterFFallback Lazy k f t = alterFYoneda k (\m q -> q <$> f m) t id
alterFFallback Strict k f t = alterFYoneda k (\m q -> q . forceMaybe <$> f m) t id
where
forceMaybe Nothing = Nothing
forceMaybe may@(Just !_) = may
{-# NOINLINE alterFFallback #-}
alterFYoneda :: Ord k =>
k -> (Maybe a -> (Maybe a -> b) -> f b) -> Map k a -> (Map k a -> b) -> f b
alterFYoneda = go
where
go :: Ord k =>
k -> (Maybe a -> (Maybe a -> b) -> f b) -> Map k a -> (Map k a -> b) -> f b
go !k f Tip g = f Nothing $ \ mx -> case mx of
Nothing -> g Tip
Just x -> g (singleton k x)
go k f (Bin sx kx x l r) g = case compare k kx of
LT -> go k f l (\m -> g (balance kx x m r))
GT -> go k f r (\m -> g (balance kx x l m))
EQ -> f (Just x) $ \ mx' -> case mx' of
Just x' -> g (Bin sx kx x' l r)
Nothing -> g (glue l r)
{-# INLINE alterFYoneda #-}
#endif
findIndex :: Ord k => k -> Map k a -> Int
findIndex :: k -> Map k a -> Int
findIndex = Int -> k -> Map k a -> Int
forall k a. Ord k => Int -> k -> Map k a -> Int
Evidence bound by a type signature of the constraint type Ord k
go Int
0
where
go :: Ord k => Int -> k -> Map k a -> Int
go :: Int -> k -> Map k a -> Int
go !Int
_ !k
_ Map k a
Tip = [Char] -> Int
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.findIndex: element is not in the map"
go Int
idx k
k (Bin Int
_ k
kx a
_ Map k a
l Map k a
r) = case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> Int -> k -> Map k a -> Int
forall k a. Ord k => Int -> k -> Map k a -> Int
Evidence bound by a type signature of the constraint type Ord k
go Int
idx k
k Map k a
l
Ordering
GT -> Int -> k -> Map k a -> Int
forall k a. Ord k => Int -> k -> Map k a -> Int
Evidence bound by a type signature of the constraint type Ord k
go (Int
idx Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
1) k
k Map k a
r
Ordering
EQ -> Int
idx Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
#if __GLASGOW_HASKELL__
{-# INLINABLE findIndex #-}
#endif
lookupIndex :: Ord k => k -> Map k a -> Maybe Int
lookupIndex :: k -> Map k a -> Maybe Int
lookupIndex = Int -> k -> Map k a -> Maybe Int
forall k a. Ord k => Int -> k -> Map k a -> Maybe Int
Evidence bound by a type signature of the constraint type Ord k
go Int
0
where
go :: Ord k => Int -> k -> Map k a -> Maybe Int
go :: Int -> k -> Map k a -> Maybe Int
go !Int
_ !k
_ Map k a
Tip = Maybe Int
forall a. Maybe a
Nothing
go Int
idx k
k (Bin Int
_ k
kx a
_ Map k a
l Map k a
r) = case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> Int -> k -> Map k a -> Maybe Int
forall k a. Ord k => Int -> k -> Map k a -> Maybe Int
Evidence bound by a type signature of the constraint type Ord k
go Int
idx k
k Map k a
l
Ordering
GT -> Int -> k -> Map k a -> Maybe Int
forall k a. Ord k => Int -> k -> Map k a -> Maybe Int
Evidence bound by a type signature of the constraint type Ord k
go (Int
idx Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
1) k
k Map k a
r
Ordering
EQ -> Int -> Maybe Int
forall a. a -> Maybe a
Just (Int -> Maybe Int) -> Int -> Maybe Int
forall a b. (a -> b) -> a -> b
$! Int
idx Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
#if __GLASGOW_HASKELL__
{-# INLINABLE lookupIndex #-}
#endif
elemAt :: Int -> Map k a -> (k,a)
elemAt :: Int -> Map k a -> (k, a)
elemAt !Int
_ Map k a
Tip = [Char] -> (k, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.elemAt: index out of range"
elemAt Int
i (Bin Int
_ k
kx a
x Map k a
l Map k a
r)
= case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
sizeL of
Ordering
LT -> Int -> Map k a -> (k, a)
forall k a. Int -> Map k a -> (k, a)
elemAt Int
i Map k a
l
Ordering
GT -> Int -> Map k a -> (k, a)
forall k a. Int -> Map k a -> (k, a)
elemAt (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
sizeLInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
1) Map k a
r
Ordering
EQ -> (k
kx,a
x)
where
sizeL :: Int
sizeL = Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
take :: Int -> Map k a -> Map k a
take :: Int -> Map k a -> Map k a
take Int
i Map k a
m | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
>= Map k a -> Int
forall k a. Map k a -> Int
size Map k a
m = Map k a
m
take Int
i0 Map k a
m0 = Int -> Map k a -> Map k a
forall {k} {a}. Int -> Map k a -> Map k a
go Int
i0 Map k a
m0
where
go :: Int -> Map k a -> Map k a
go Int
i !Map k a
_ | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
0 = Map k a
forall k a. Map k a
Tip
go !Int
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
go Int
i (Bin Int
_ k
kx a
x Map k a
l Map k a
r) =
case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
sizeL of
Ordering
LT -> Int -> Map k a -> Map k a
go Int
i Map k a
l
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l (Int -> Map k a -> Map k a
go (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
sizeL Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1) Map k a
r)
Ordering
EQ -> Map k a
l
where sizeL :: Int
sizeL = Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
drop :: Int -> Map k a -> Map k a
drop :: Int -> Map k a -> Map k a
drop Int
i Map k a
m | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
>= Map k a -> Int
forall k a. Map k a -> Int
size Map k a
m = Map k a
forall k a. Map k a
Tip
drop Int
i0 Map k a
m0 = Int -> Map k a -> Map k a
forall {k} {a}. Int -> Map k a -> Map k a
go Int
i0 Map k a
m0
where
go :: Int -> Map k a -> Map k a
go Int
i Map k a
m | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
0 = Map k a
m
go !Int
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
go Int
i (Bin Int
_ k
kx a
x Map k a
l Map k a
r) =
case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
sizeL of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x (Int -> Map k a -> Map k a
go Int
i Map k a
l) Map k a
r
Ordering
GT -> Int -> Map k a -> Map k a
go (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
sizeL Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1) Map k a
r
Ordering
EQ -> k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMin k
kx a
x Map k a
r
where sizeL :: Int
sizeL = Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
splitAt :: Int -> Map k a -> (Map k a, Map k a)
splitAt :: Int -> Map k a -> (Map k a, Map k a)
splitAt Int
i0 Map k a
m0
| Int
i0 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
>= Map k a -> Int
forall k a. Map k a -> Int
size Map k a
m0 = (Map k a
m0, Map k a
forall k a. Map k a
Tip)
| Bool
otherwise = StrictPair (Map k a) (Map k a) -> (Map k a, Map k a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Map k a) (Map k a) -> (Map k a, Map k a))
-> StrictPair (Map k a) (Map k a) -> (Map k a, Map k a)
forall a b. (a -> b) -> a -> b
$ Int -> Map k a -> StrictPair (Map k a) (Map k a)
forall {k} {a}. Int -> Map k a -> StrictPair (Map k a) (Map k a)
go Int
i0 Map k a
m0
where
go :: Int -> Map k a -> StrictPair (Map k a) (Map k a)
go Int
i Map k a
m | Int
i Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Int
0 = Map k a
forall k a. Map k a
Tip Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
m
go !Int
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
forall k a. Map k a
Tip
go Int
i (Bin Int
_ k
kx a
x Map k a
l Map k a
r)
= case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
sizeL of
Ordering
LT -> case Int -> Map k a -> StrictPair (Map k a) (Map k a)
go Int
i Map k a
l of
Map k a
ll :*: Map k a
lr -> Map k a
ll Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
lr Map k a
r
Ordering
GT -> case Int -> Map k a -> StrictPair (Map k a) (Map k a)
go (Int
i Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
sizeL Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
- Int
1) Map k a
r of
Map k a
rl :*: Map k a
rr -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
rl Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
rr
Ordering
EQ -> Map k a
l Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMin k
kx a
x Map k a
r
where sizeL :: Int
sizeL = Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
updateAt :: (k -> a -> Maybe a) -> Int -> Map k a -> Map k a
updateAt :: (k -> a -> Maybe a) -> Int -> Map k a -> Map k a
updateAt k -> a -> Maybe a
f !Int
i Map k a
t =
case Map k a
t of
Map k a
Tip -> [Char] -> Map k a
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.updateAt: index out of range"
Bin Int
sx k
kx a
x Map k a
l Map k a
r -> case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
sizeL of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x ((k -> a -> Maybe a) -> Int -> Map k a -> Map k a
forall k a. (k -> a -> Maybe a) -> Int -> Map k a -> Map k a
updateAt k -> a -> Maybe a
f Int
i Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l ((k -> a -> Maybe a) -> Int -> Map k a -> Map k a
forall k a. (k -> a -> Maybe a) -> Int -> Map k a -> Map k a
updateAt k -> a -> Maybe a
f (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
sizeLInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
1) Map k a
r)
Ordering
EQ -> case k -> a -> Maybe a
f k
kx a
x of
Just a
x' -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
l Map k a
r
Maybe a
Nothing -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
where
sizeL :: Int
sizeL = Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
deleteAt :: Int -> Map k a -> Map k a
deleteAt :: Int -> Map k a -> Map k a
deleteAt !Int
i Map k a
t =
case Map k a
t of
Map k a
Tip -> [Char] -> Map k a
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.deleteAt: index out of range"
Bin Int
_ k
kx a
x Map k a
l Map k a
r -> case Int -> Int -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type Ord Int
compare Int
i Int
sizeL of
Ordering
LT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x (Int -> Map k a -> Map k a
forall {k} {a}. Int -> Map k a -> Map k a
deleteAt Int
i Map k a
l) Map k a
r
Ordering
GT -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l (Int -> Map k a -> Map k a
forall {k} {a}. Int -> Map k a -> Map k a
deleteAt (Int
iInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
sizeLInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
-Int
1) Map k a
r)
Ordering
EQ -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
where
sizeL :: Int
sizeL = Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l
lookupMinSure :: k -> a -> Map k a -> (k, a)
lookupMinSure :: k -> a -> Map k a -> (k, a)
lookupMinSure k
k a
a Map k a
Tip = (k
k, a
a)
lookupMinSure k
_ a
_ (Bin Int
_ k
k a
a Map k a
l Map k a
_) = k -> a -> Map k a -> (k, a)
forall k a. k -> a -> Map k a -> (k, a)
lookupMinSure k
k a
a Map k a
l
lookupMin :: Map k a -> Maybe (k,a)
lookupMin :: Map k a -> Maybe (k, a)
lookupMin Map k a
Tip = Maybe (k, a)
forall a. Maybe a
Nothing
lookupMin (Bin Int
_ k
k a
x Map k a
l Map k a
_) = (k, a) -> Maybe (k, a)
forall a. a -> Maybe a
Just ((k, a) -> Maybe (k, a)) -> (k, a) -> Maybe (k, a)
forall a b. (a -> b) -> a -> b
$! k -> a -> Map k a -> (k, a)
forall k a. k -> a -> Map k a -> (k, a)
lookupMinSure k
k a
x Map k a
l
findMin :: Map k a -> (k,a)
findMin :: Map k a -> (k, a)
findMin Map k a
t
| Just (k, a)
r <- Map k a -> Maybe (k, a)
forall k a. Map k a -> Maybe (k, a)
lookupMin Map k a
t = (k, a)
r
| Bool
otherwise = [Char] -> (k, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.findMin: empty map has no minimal element"
lookupMaxSure :: k -> a -> Map k a -> (k, a)
lookupMaxSure :: k -> a -> Map k a -> (k, a)
lookupMaxSure k
k a
a Map k a
Tip = (k
k, a
a)
lookupMaxSure k
_ a
_ (Bin Int
_ k
k a
a Map k a
_ Map k a
r) = k -> a -> Map k a -> (k, a)
forall k a. k -> a -> Map k a -> (k, a)
lookupMaxSure k
k a
a Map k a
r
lookupMax :: Map k a -> Maybe (k, a)
lookupMax :: Map k a -> Maybe (k, a)
lookupMax Map k a
Tip = Maybe (k, a)
forall a. Maybe a
Nothing
lookupMax (Bin Int
_ k
k a
x Map k a
_ Map k a
r) = (k, a) -> Maybe (k, a)
forall a. a -> Maybe a
Just ((k, a) -> Maybe (k, a)) -> (k, a) -> Maybe (k, a)
forall a b. (a -> b) -> a -> b
$! k -> a -> Map k a -> (k, a)
forall k a. k -> a -> Map k a -> (k, a)
lookupMaxSure k
k a
x Map k a
r
findMax :: Map k a -> (k,a)
findMax :: Map k a -> (k, a)
findMax Map k a
t
| Just (k, a)
r <- Map k a -> Maybe (k, a)
forall k a. Map k a -> Maybe (k, a)
lookupMax Map k a
t = (k, a)
r
| Bool
otherwise = [Char] -> (k, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.findMax: empty map has no maximal element"
deleteMin :: Map k a -> Map k a
deleteMin :: Map k a -> Map k a
deleteMin (Bin Int
_ k
_ a
_ Map k a
Tip Map k a
r) = Map k a
r
deleteMin (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x (Map k a -> Map k a
forall k a. Map k a -> Map k a
deleteMin Map k a
l) Map k a
r
deleteMin Map k a
Tip = Map k a
forall k a. Map k a
Tip
deleteMax :: Map k a -> Map k a
deleteMax :: Map k a -> Map k a
deleteMax (Bin Int
_ k
_ a
_ Map k a
l Map k a
Tip) = Map k a
l
deleteMax (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l (Map k a -> Map k a
forall k a. Map k a -> Map k a
deleteMax Map k a
r)
deleteMax Map k a
Tip = Map k a
forall k a. Map k a
Tip
updateMin :: (a -> Maybe a) -> Map k a -> Map k a
updateMin :: (a -> Maybe a) -> Map k a -> Map k a
updateMin a -> Maybe a
f Map k a
m
= (k -> a -> Maybe a) -> Map k a -> Map k a
forall k a. (k -> a -> Maybe a) -> Map k a -> Map k a
updateMinWithKey (\k
_ a
x -> a -> Maybe a
f a
x) Map k a
m
updateMax :: (a -> Maybe a) -> Map k a -> Map k a
updateMax :: (a -> Maybe a) -> Map k a -> Map k a
updateMax a -> Maybe a
f Map k a
m
= (k -> a -> Maybe a) -> Map k a -> Map k a
forall k a. (k -> a -> Maybe a) -> Map k a -> Map k a
updateMaxWithKey (\k
_ a
x -> a -> Maybe a
f a
x) Map k a
m
updateMinWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a
updateMinWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a
updateMinWithKey k -> a -> Maybe a
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
updateMinWithKey k -> a -> Maybe a
f (Bin Int
sx k
kx a
x Map k a
Tip Map k a
r) = case k -> a -> Maybe a
f k
kx a
x of
Maybe a
Nothing -> Map k a
r
Just a
x' -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
forall k a. Map k a
Tip Map k a
r
updateMinWithKey k -> a -> Maybe a
f (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x ((k -> a -> Maybe a) -> Map k a -> Map k a
forall k a. (k -> a -> Maybe a) -> Map k a -> Map k a
updateMinWithKey k -> a -> Maybe a
f Map k a
l) Map k a
r
updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a
updateMaxWithKey :: (k -> a -> Maybe a) -> Map k a -> Map k a
updateMaxWithKey k -> a -> Maybe a
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
updateMaxWithKey k -> a -> Maybe a
f (Bin Int
sx k
kx a
x Map k a
l Map k a
Tip) = case k -> a -> Maybe a
f k
kx a
x of
Maybe a
Nothing -> Map k a
l
Just a
x' -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
x' Map k a
l Map k a
forall k a. Map k a
Tip
updateMaxWithKey k -> a -> Maybe a
f (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kx a
x Map k a
l ((k -> a -> Maybe a) -> Map k a -> Map k a
forall k a. (k -> a -> Maybe a) -> Map k a -> Map k a
updateMaxWithKey k -> a -> Maybe a
f Map k a
r)
minViewWithKey :: Map k a -> Maybe ((k,a), Map k a)
minViewWithKey :: Map k a -> Maybe ((k, a), Map k a)
minViewWithKey Map k a
Tip = Maybe ((k, a), Map k a)
forall a. Maybe a
Nothing
minViewWithKey (Bin Int
_ k
k a
x Map k a
l Map k a
r) = ((k, a), Map k a) -> Maybe ((k, a), Map k a)
forall a. a -> Maybe a
Just (((k, a), Map k a) -> Maybe ((k, a), Map k a))
-> ((k, a), Map k a) -> Maybe ((k, a), Map k a)
forall a b. (a -> b) -> a -> b
$
case k -> a -> Map k a -> Map k a -> MinView k a
forall k a. k -> a -> Map k a -> Map k a -> MinView k a
minViewSure k
k a
x Map k a
l Map k a
r of
MinView k
km a
xm Map k a
t -> ((k
km, a
xm), Map k a
t)
{-# INLINE minViewWithKey #-}
maxViewWithKey :: Map k a -> Maybe ((k,a), Map k a)
maxViewWithKey :: Map k a -> Maybe ((k, a), Map k a)
maxViewWithKey Map k a
Tip = Maybe ((k, a), Map k a)
forall a. Maybe a
Nothing
maxViewWithKey (Bin Int
_ k
k a
x Map k a
l Map k a
r) = ((k, a), Map k a) -> Maybe ((k, a), Map k a)
forall a. a -> Maybe a
Just (((k, a), Map k a) -> Maybe ((k, a), Map k a))
-> ((k, a), Map k a) -> Maybe ((k, a), Map k a)
forall a b. (a -> b) -> a -> b
$
case k -> a -> Map k a -> Map k a -> MaxView k a
forall k a. k -> a -> Map k a -> Map k a -> MaxView k a
maxViewSure k
k a
x Map k a
l Map k a
r of
MaxView k
km a
xm Map k a
t -> ((k
km, a
xm), Map k a
t)
{-# INLINE maxViewWithKey #-}
minView :: Map k a -> Maybe (a, Map k a)
minView :: Map k a -> Maybe (a, Map k a)
minView Map k a
t = case Map k a -> Maybe ((k, a), Map k a)
forall k a. Map k a -> Maybe ((k, a), Map k a)
minViewWithKey Map k a
t of
Maybe ((k, a), Map k a)
Nothing -> Maybe (a, Map k a)
forall a. Maybe a
Nothing
Just ~((k
_, a
x), Map k a
t') -> (a, Map k a) -> Maybe (a, Map k a)
forall a. a -> Maybe a
Just (a
x, Map k a
t')
maxView :: Map k a -> Maybe (a, Map k a)
maxView :: Map k a -> Maybe (a, Map k a)
maxView Map k a
t = case Map k a -> Maybe ((k, a), Map k a)
forall k a. Map k a -> Maybe ((k, a), Map k a)
maxViewWithKey Map k a
t of
Maybe ((k, a), Map k a)
Nothing -> Maybe (a, Map k a)
forall a. Maybe a
Nothing
Just ~((k
_, a
x), Map k a
t') -> (a, Map k a) -> Maybe (a, Map k a)
forall a. a -> Maybe a
Just (a
x, Map k a
t')
unions :: (Foldable f, Ord k) => f (Map k a) -> Map k a
unions :: f (Map k a) -> Map k a
unions f (Map k a)
ts
= (Map k a -> Map k a -> Map k a)
-> Map k a -> f (Map k a) -> Map k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Evidence bound by a type signature of the constraint type Foldable f
Foldable.foldl' Map k a -> Map k a -> Map k a
forall k v. Ord k => Map k v -> Map k v -> Map k v
Evidence bound by a type signature of the constraint type Ord k
union Map k a
forall k a. Map k a
empty f (Map k a)
ts
#if __GLASGOW_HASKELL__
{-# INLINABLE unions #-}
#endif
unionsWith :: (Foldable f, Ord k) => (a->a->a) -> f (Map k a) -> Map k a
unionsWith :: (a -> a -> a) -> f (Map k a) -> Map k a
unionsWith a -> a -> a
f f (Map k a)
ts
= (Map k a -> Map k a -> Map k a)
-> Map k a -> f (Map k a) -> Map k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Evidence bound by a type signature of the constraint type Foldable f
Foldable.foldl' ((a -> a -> a) -> Map k a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
unionWith a -> a -> a
f) Map k a
forall k a. Map k a
empty f (Map k a)
ts
#if __GLASGOW_HASKELL__
{-# INLINABLE unionsWith #-}
#endif
union :: Ord k => Map k a -> Map k a -> Map k a
union :: Map k a -> Map k a -> Map k a
union Map k a
t1 Map k a
Tip = Map k a
t1
union Map k a
t1 (Bin Int
_ k
k a
x Map k a
Tip Map k a
Tip) = k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insertR k
k a
x Map k a
t1
union (Bin Int
_ k
k a
x Map k a
Tip Map k a
Tip) Map k a
t2 = k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insert k
k a
x Map k a
t2
union Map k a
Tip Map k a
t2 = Map k a
t2
union t1 :: Map k a
t1@(Bin Int
_ k
k1 a
x1 Map k a
l1 Map k a
r1) Map k a
t2 = case k -> Map k a -> (Map k a, Map k a)
forall k a. Ord k => k -> Map k a -> (Map k a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
split k
k1 Map k a
t2 of
(Map k a
l2, Map k a
r2) | Map k a
l1l2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l1 Bool -> Bool -> Bool
&& Map k a
r1r2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r1 -> Map k a
t1
| Bool
otherwise -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k1 a
x1 Map k a
l1l2 Map k a
r1r2
where !l1l2 :: Map k a
l1l2 = Map k a -> Map k a -> Map k a
forall k v. Ord k => Map k v -> Map k v -> Map k v
Evidence bound by a type signature of the constraint type Ord k
union Map k a
l1 Map k a
l2
!r1r2 :: Map k a
r1r2 = Map k a -> Map k a -> Map k a
forall k v. Ord k => Map k v -> Map k v -> Map k v
Evidence bound by a type signature of the constraint type Ord k
union Map k a
r1 Map k a
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE union #-}
#endif
unionWith :: Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
unionWith :: (a -> a -> a) -> Map k a -> Map k a -> Map k a
unionWith a -> a -> a
_f Map k a
t1 Map k a
Tip = Map k a
t1
unionWith a -> a -> a
f Map k a
t1 (Bin Int
_ k
k a
x Map k a
Tip Map k a
Tip) = (a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insertWithR a -> a -> a
f k
k a
x Map k a
t1
unionWith a -> a -> a
f (Bin Int
_ k
k a
x Map k a
Tip Map k a
Tip) Map k a
t2 = (a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insertWith a -> a -> a
f k
k a
x Map k a
t2
unionWith a -> a -> a
_f Map k a
Tip Map k a
t2 = Map k a
t2
unionWith a -> a -> a
f (Bin Int
_ k
k1 a
x1 Map k a
l1 Map k a
r1) Map k a
t2 = case k -> Map k a -> (Map k a, Maybe a, Map k a)
forall k a. Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitLookup k
k1 Map k a
t2 of
(Map k a
l2, Maybe a
mb, Map k a
r2) -> case Maybe a
mb of
Maybe a
Nothing -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k1 a
x1 Map k a
l1l2 Map k a
r1r2
Just a
x2 -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k1 (a -> a -> a
f a
x1 a
x2) Map k a
l1l2 Map k a
r1r2
where !l1l2 :: Map k a
l1l2 = (a -> a -> a) -> Map k a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
unionWith a -> a -> a
f Map k a
l1 Map k a
l2
!r1r2 :: Map k a
r1r2 = (a -> a -> a) -> Map k a -> Map k a -> Map k a
forall k a. Ord k => (a -> a -> a) -> Map k a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
unionWith a -> a -> a
f Map k a
r1 Map k a
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE unionWith #-}
#endif
unionWithKey :: Ord k => (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a
unionWithKey :: (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a
unionWithKey k -> a -> a -> a
_f Map k a
t1 Map k a
Tip = Map k a
t1
unionWithKey k -> a -> a -> a
f Map k a
t1 (Bin Int
_ k
k a
x Map k a
Tip Map k a
Tip) = (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insertWithKeyR k -> a -> a -> a
f k
k a
x Map k a
t1
unionWithKey k -> a -> a -> a
f (Bin Int
_ k
k a
x Map k a
Tip Map k a
Tip) Map k a
t2 = (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insertWithKey k -> a -> a -> a
f k
k a
x Map k a
t2
unionWithKey k -> a -> a -> a
_f Map k a
Tip Map k a
t2 = Map k a
t2
unionWithKey k -> a -> a -> a
f (Bin Int
_ k
k1 a
x1 Map k a
l1 Map k a
r1) Map k a
t2 = case k -> Map k a -> (Map k a, Maybe a, Map k a)
forall k a. Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitLookup k
k1 Map k a
t2 of
(Map k a
l2, Maybe a
mb, Map k a
r2) -> case Maybe a
mb of
Maybe a
Nothing -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k1 a
x1 Map k a
l1l2 Map k a
r1r2
Just a
x2 -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k1 (k -> a -> a -> a
f k
k1 a
x1 a
x2) Map k a
l1l2 Map k a
r1r2
where !l1l2 :: Map k a
l1l2 = (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> Map k a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
unionWithKey k -> a -> a -> a
f Map k a
l1 Map k a
l2
!r1r2 :: Map k a
r1r2 = (k -> a -> a -> a) -> Map k a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> Map k a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
unionWithKey k -> a -> a -> a
f Map k a
r1 Map k a
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE unionWithKey #-}
#endif
difference :: Ord k => Map k a -> Map k b -> Map k a
difference :: Map k a -> Map k b -> Map k a
difference Map k a
Tip Map k b
_ = Map k a
forall k a. Map k a
Tip
difference Map k a
t1 Map k b
Tip = Map k a
t1
difference Map k a
t1 (Bin Int
_ k
k b
_ Map k b
l2 Map k b
r2) = case k -> Map k a -> (Map k a, Map k a)
forall k a. Ord k => k -> Map k a -> (Map k a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
split k
k Map k a
t1 of
(Map k a
l1, Map k a
r1)
| Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l1l2 Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Map k a -> Int
forall k a. Map k a -> Int
size Map k a
r1r2 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Map k a -> Int
forall k a. Map k a -> Int
size Map k a
t1 -> Map k a
t1
| Bool
otherwise -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l1l2 Map k a
r1r2
where
!l1l2 :: Map k a
l1l2 = Map k a -> Map k b -> Map k a
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Evidence bound by a type signature of the constraint type Ord k
difference Map k a
l1 Map k b
l2
!r1r2 :: Map k a
r1r2 = Map k a -> Map k b -> Map k a
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Evidence bound by a type signature of the constraint type Ord k
difference Map k a
r1 Map k b
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE difference #-}
#endif
withoutKeys :: Ord k => Map k a -> Set k -> Map k a
withoutKeys :: Map k a -> Set k -> Map k a
withoutKeys Map k a
Tip Set k
_ = Map k a
forall k a. Map k a
Tip
withoutKeys Map k a
m Set k
Set.Tip = Map k a
m
withoutKeys Map k a
m (Set.Bin Int
_ k
k Set k
ls Set k
rs) = case k -> Map k a -> (Map k a, Bool, Map k a)
forall k a. Ord k => k -> Map k a -> (Map k a, Bool, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitMember k
k Map k a
m of
(Map k a
lm, Bool
b, Map k a
rm)
| Bool -> Bool
not Bool
b Bool -> Bool -> Bool
&& Map k a
lm' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
lm Bool -> Bool -> Bool
&& Map k a
rm' Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
rm -> Map k a
m
| Bool
otherwise -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
lm' Map k a
rm'
where
!lm' :: Map k a
lm' = Map k a -> Set k -> Map k a
forall k a. Ord k => Map k a -> Set k -> Map k a
Evidence bound by a type signature of the constraint type Ord k
withoutKeys Map k a
lm Set k
ls
!rm' :: Map k a
rm' = Map k a -> Set k -> Map k a
forall k a. Ord k => Map k a -> Set k -> Map k a
Evidence bound by a type signature of the constraint type Ord k
withoutKeys Map k a
rm Set k
rs
#if __GLASGOW_HASKELL__
{-# INLINABLE withoutKeys #-}
#endif
differenceWith :: Ord k => (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a
differenceWith :: (a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a
differenceWith a -> b -> Maybe a
f = SimpleWhenMissing k a a
-> SimpleWhenMissing k b a
-> SimpleWhenMatched k a b a
-> Map k a
-> Map k b
-> Map k a
forall k a c b.
Ord k =>
SimpleWhenMissing k a c
-> SimpleWhenMissing k b c
-> SimpleWhenMatched k a b c
-> Map k a
-> Map k b
-> Map k c
Evidence bound by a type signature of the constraint type Ord k
merge SimpleWhenMissing k a a
forall (f :: * -> *) k x. Applicative f => WhenMissing f k x x
External instance of the constraint type Applicative Identity
preserveMissing SimpleWhenMissing k b a
forall (f :: * -> *) k x y. Applicative f => WhenMissing f k x y
External instance of the constraint type Applicative Identity
dropMissing (SimpleWhenMatched k a b a -> Map k a -> Map k b -> Map k a)
-> SimpleWhenMatched k a b a -> Map k a -> Map k b -> Map k a
forall a b. (a -> b) -> a -> b
$
(k -> a -> b -> Maybe a) -> SimpleWhenMatched k a b a
forall (f :: * -> *) k x y z.
Applicative f =>
(k -> x -> y -> Maybe z) -> WhenMatched f k x y z
External instance of the constraint type Applicative Identity
zipWithMaybeMatched (\k
_ a
x b
y -> a -> b -> Maybe a
f a
x b
y)
#if __GLASGOW_HASKELL__
{-# INLINABLE differenceWith #-}
#endif
differenceWithKey :: Ord k => (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a
differenceWithKey :: (k -> a -> b -> Maybe a) -> Map k a -> Map k b -> Map k a
differenceWithKey k -> a -> b -> Maybe a
f =
SimpleWhenMissing k a a
-> SimpleWhenMissing k b a
-> SimpleWhenMatched k a b a
-> Map k a
-> Map k b
-> Map k a
forall k a c b.
Ord k =>
SimpleWhenMissing k a c
-> SimpleWhenMissing k b c
-> SimpleWhenMatched k a b c
-> Map k a
-> Map k b
-> Map k c
Evidence bound by a type signature of the constraint type Ord k
merge SimpleWhenMissing k a a
forall (f :: * -> *) k x. Applicative f => WhenMissing f k x x
External instance of the constraint type Applicative Identity
preserveMissing SimpleWhenMissing k b a
forall (f :: * -> *) k x y. Applicative f => WhenMissing f k x y
External instance of the constraint type Applicative Identity
dropMissing ((k -> a -> b -> Maybe a) -> SimpleWhenMatched k a b a
forall (f :: * -> *) k x y z.
Applicative f =>
(k -> x -> y -> Maybe z) -> WhenMatched f k x y z
External instance of the constraint type Applicative Identity
zipWithMaybeMatched k -> a -> b -> Maybe a
f)
#if __GLASGOW_HASKELL__
{-# INLINABLE differenceWithKey #-}
#endif
intersection :: Ord k => Map k a -> Map k b -> Map k a
intersection :: Map k a -> Map k b -> Map k a
intersection Map k a
Tip Map k b
_ = Map k a
forall k a. Map k a
Tip
intersection Map k a
_ Map k b
Tip = Map k a
forall k a. Map k a
Tip
intersection t1 :: Map k a
t1@(Bin Int
_ k
k a
x Map k a
l1 Map k a
r1) Map k b
t2
| Bool
mb = if Map k a
l1l2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l1 Bool -> Bool -> Bool
&& Map k a
r1r2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r1
then Map k a
t1
else k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k a
x Map k a
l1l2 Map k a
r1r2
| Bool
otherwise = Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l1l2 Map k a
r1r2
where
!(Map k b
l2, Bool
mb, Map k b
r2) = k -> Map k b -> (Map k b, Bool, Map k b)
forall k a. Ord k => k -> Map k a -> (Map k a, Bool, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitMember k
k Map k b
t2
!l1l2 :: Map k a
l1l2 = Map k a -> Map k b -> Map k a
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Evidence bound by a type signature of the constraint type Ord k
intersection Map k a
l1 Map k b
l2
!r1r2 :: Map k a
r1r2 = Map k a -> Map k b -> Map k a
forall k a b. Ord k => Map k a -> Map k b -> Map k a
Evidence bound by a type signature of the constraint type Ord k
intersection Map k a
r1 Map k b
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE intersection #-}
#endif
restrictKeys :: Ord k => Map k a -> Set k -> Map k a
restrictKeys :: Map k a -> Set k -> Map k a
restrictKeys Map k a
Tip Set k
_ = Map k a
forall k a. Map k a
Tip
restrictKeys Map k a
_ Set k
Set.Tip = Map k a
forall k a. Map k a
Tip
restrictKeys m :: Map k a
m@(Bin Int
_ k
k a
x Map k a
l1 Map k a
r1) Set k
s
| Bool
b = if Map k a
l1l2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l1 Bool -> Bool -> Bool
&& Map k a
r1r2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r1
then Map k a
m
else k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k a
x Map k a
l1l2 Map k a
r1r2
| Bool
otherwise = Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l1l2 Map k a
r1r2
where
!(Set k
l2, Bool
b, Set k
r2) = k -> Set k -> (Set k, Bool, Set k)
forall a. Ord a => a -> Set a -> (Set a, Bool, Set a)
Evidence bound by a type signature of the constraint type Ord k
Set.splitMember k
k Set k
s
!l1l2 :: Map k a
l1l2 = Map k a -> Set k -> Map k a
forall k a. Ord k => Map k a -> Set k -> Map k a
Evidence bound by a type signature of the constraint type Ord k
restrictKeys Map k a
l1 Set k
l2
!r1r2 :: Map k a
r1r2 = Map k a -> Set k -> Map k a
forall k a. Ord k => Map k a -> Set k -> Map k a
Evidence bound by a type signature of the constraint type Ord k
restrictKeys Map k a
r1 Set k
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE restrictKeys #-}
#endif
intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c
intersectionWith :: (a -> b -> c) -> Map k a -> Map k b -> Map k c
intersectionWith a -> b -> c
_f Map k a
Tip Map k b
_ = Map k c
forall k a. Map k a
Tip
intersectionWith a -> b -> c
_f Map k a
_ Map k b
Tip = Map k c
forall k a. Map k a
Tip
intersectionWith a -> b -> c
f (Bin Int
_ k
k a
x1 Map k a
l1 Map k a
r1) Map k b
t2 = case Maybe b
mb of
Just b
x2 -> k -> c -> Map k c -> Map k c -> Map k c
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k (a -> b -> c
f a
x1 b
x2) Map k c
l1l2 Map k c
r1r2
Maybe b
Nothing -> Map k c -> Map k c -> Map k c
forall k a. Map k a -> Map k a -> Map k a
link2 Map k c
l1l2 Map k c
r1r2
where
!(Map k b
l2, Maybe b
mb, Map k b
r2) = k -> Map k b -> (Map k b, Maybe b, Map k b)
forall k a. Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitLookup k
k Map k b
t2
!l1l2 :: Map k c
l1l2 = (a -> b -> c) -> Map k a -> Map k b -> Map k c
forall k a b c.
Ord k =>
(a -> b -> c) -> Map k a -> Map k b -> Map k c
Evidence bound by a type signature of the constraint type Ord k
intersectionWith a -> b -> c
f Map k a
l1 Map k b
l2
!r1r2 :: Map k c
r1r2 = (a -> b -> c) -> Map k a -> Map k b -> Map k c
forall k a b c.
Ord k =>
(a -> b -> c) -> Map k a -> Map k b -> Map k c
Evidence bound by a type signature of the constraint type Ord k
intersectionWith a -> b -> c
f Map k a
r1 Map k b
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE intersectionWith #-}
#endif
intersectionWithKey :: Ord k => (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
intersectionWithKey :: (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
intersectionWithKey k -> a -> b -> c
_f Map k a
Tip Map k b
_ = Map k c
forall k a. Map k a
Tip
intersectionWithKey k -> a -> b -> c
_f Map k a
_ Map k b
Tip = Map k c
forall k a. Map k a
Tip
intersectionWithKey k -> a -> b -> c
f (Bin Int
_ k
k a
x1 Map k a
l1 Map k a
r1) Map k b
t2 = case Maybe b
mb of
Just b
x2 -> k -> c -> Map k c -> Map k c -> Map k c
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
k (k -> a -> b -> c
f k
k a
x1 b
x2) Map k c
l1l2 Map k c
r1r2
Maybe b
Nothing -> Map k c -> Map k c -> Map k c
forall k a. Map k a -> Map k a -> Map k a
link2 Map k c
l1l2 Map k c
r1r2
where
!(Map k b
l2, Maybe b
mb, Map k b
r2) = k -> Map k b -> (Map k b, Maybe b, Map k b)
forall k a. Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitLookup k
k Map k b
t2
!l1l2 :: Map k c
l1l2 = (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
forall k a b c.
Ord k =>
(k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
Evidence bound by a type signature of the constraint type Ord k
intersectionWithKey k -> a -> b -> c
f Map k a
l1 Map k b
l2
!r1r2 :: Map k c
r1r2 = (k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
forall k a b c.
Ord k =>
(k -> a -> b -> c) -> Map k a -> Map k b -> Map k c
Evidence bound by a type signature of the constraint type Ord k
intersectionWithKey k -> a -> b -> c
f Map k a
r1 Map k b
r2
#if __GLASGOW_HASKELL__
{-# INLINABLE intersectionWithKey #-}
#endif
disjoint :: Ord k => Map k a -> Map k b -> Bool
disjoint :: Map k a -> Map k b -> Bool
disjoint Map k a
Tip Map k b
_ = Bool
True
disjoint Map k a
_ Map k b
Tip = Bool
True
disjoint (Bin Int
1 k
k a
_ Map k a
_ Map k a
_) Map k b
t = k
k k -> Map k b -> Bool
forall {t} {a}. Ord t => t -> Map t a -> Bool
Evidence bound by a type signature of the constraint type Ord k
`notMember` Map k b
t
disjoint (Bin Int
_ k
k a
_ Map k a
l Map k a
r) Map k b
t
= Bool -> Bool
not Bool
found Bool -> Bool -> Bool
&& Map k a -> Map k b -> Bool
forall k a b. Ord k => Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord k
disjoint Map k a
l Map k b
lt Bool -> Bool -> Bool
&& Map k a -> Map k b -> Bool
forall k a b. Ord k => Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord k
disjoint Map k a
r Map k b
gt
where
(Map k b
lt,Bool
found,Map k b
gt) = k -> Map k b -> (Map k b, Bool, Map k b)
forall k a. Ord k => k -> Map k a -> (Map k a, Bool, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitMember k
k Map k b
t
#if !MIN_VERSION_base (4,8,0)
newtype Identity a = Identity { runIdentity :: a }
#if __GLASGOW_HASKELL__ == 708
instance Functor Identity where
fmap = coerce
instance Applicative Identity where
(<*>) = coerce
pure = Identity
#else
instance Functor Identity where
fmap f (Identity a) = Identity (f a)
instance Applicative Identity where
Identity f <*> Identity x = Identity (f x)
pure = Identity
#endif
#endif
data WhenMissing f k x y = WhenMissing
{ WhenMissing f k x y -> Map k x -> f (Map k y)
missingSubtree :: Map k x -> f (Map k y)
, WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey :: k -> x -> f (Maybe y)}
instance (Applicative f, Monad f) => Functor (WhenMissing f k x) where
fmap :: (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b
fmap = (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b
forall (f :: * -> *) a b k x.
(Applicative f, Monad f) =>
(a -> b) -> WhenMissing f k x a -> WhenMissing f k x b
Evidence bound by a type signature of the constraint type Monad f
Evidence bound by a type signature of the constraint type Applicative f
mapWhenMissing
{-# INLINE fmap #-}
instance (Applicative f, Monad f)
=> Category.Category (WhenMissing f k) where
id :: WhenMissing f k a a
id = WhenMissing f k a a
forall (f :: * -> *) k x. Applicative f => WhenMissing f k x x
Evidence bound by a type signature of the constraint type Applicative f
preserveMissing
WhenMissing f k b c
f . :: WhenMissing f k b c -> WhenMissing f k a b -> WhenMissing f k a c
. WhenMissing f k a b
g = (k -> a -> f (Maybe c)) -> WhenMissing f k a c
forall (f :: * -> *) k x y.
Applicative f =>
(k -> x -> f (Maybe y)) -> WhenMissing f k x y
Evidence bound by a type signature of the constraint type Applicative f
traverseMaybeMissing ((k -> a -> f (Maybe c)) -> WhenMissing f k a c)
-> (k -> a -> f (Maybe c)) -> WhenMissing f k a c
forall a b. (a -> b) -> a -> b
$
\ k
k a
x -> WhenMissing f k a b -> k -> a -> f (Maybe b)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k a b
g k
k a
x f (Maybe b) -> (Maybe b -> f (Maybe c)) -> f (Maybe c)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Evidence bound by a type signature of the constraint type Monad f
>>= \Maybe b
y ->
case Maybe b
y of
Maybe b
Nothing -> Maybe c -> f (Maybe c)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure Maybe c
forall a. Maybe a
Nothing
Just b
q -> WhenMissing f k b c -> k -> b -> f (Maybe c)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k b c
f k
k b
q
{-# INLINE id #-}
{-# INLINE (.) #-}
instance (Applicative f, Monad f) => Applicative (WhenMissing f k x) where
pure :: a -> WhenMissing f k x a
pure a
x = (k -> x -> a) -> WhenMissing f k x a
forall (f :: * -> *) k x y.
Applicative f =>
(k -> x -> y) -> WhenMissing f k x y
Evidence bound by a type signature of the constraint type Applicative f
mapMissing (\ k
_ x
_ -> a
x)
WhenMissing f k x (a -> b)
f <*> :: WhenMissing f k x (a -> b)
-> WhenMissing f k x a -> WhenMissing f k x b
<*> WhenMissing f k x a
g = (k -> x -> f (Maybe b)) -> WhenMissing f k x b
forall (f :: * -> *) k x y.
Applicative f =>
(k -> x -> f (Maybe y)) -> WhenMissing f k x y
Evidence bound by a type signature of the constraint type Applicative f
traverseMaybeMissing ((k -> x -> f (Maybe b)) -> WhenMissing f k x b)
-> (k -> x -> f (Maybe b)) -> WhenMissing f k x b
forall a b. (a -> b) -> a -> b
$ \k
k x
x -> do
Maybe (a -> b)
res1 <- WhenMissing f k x (a -> b) -> k -> x -> f (Maybe (a -> b))
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k x (a -> b)
f k
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
Evidence bound by a type signature of the constraint type Applicative f
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
Evidence bound by a type signature of the constraint type Applicative f
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
External instance of the constraint type Functor Maybe
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
Evidence bound by a type signature of the constraint type Monad f
=<< WhenMissing f k x a -> k -> x -> f (Maybe a)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k x a
g k
k x
x
{-# INLINE pure #-}
{-# INLINE (<*>) #-}
instance (Applicative f, Monad f) => Monad (WhenMissing f k x) where
#if !MIN_VERSION_base(4,8,0)
return = pure
#endif
WhenMissing f k x a
m >>= :: WhenMissing f k x a
-> (a -> WhenMissing f k x b) -> WhenMissing f k x b
>>= a -> WhenMissing f k x b
f = (k -> x -> f (Maybe b)) -> WhenMissing f k x b
forall (f :: * -> *) k x y.
Applicative f =>
(k -> x -> f (Maybe y)) -> WhenMissing f k x y
Evidence bound by a type signature of the constraint type Applicative f
traverseMaybeMissing ((k -> x -> f (Maybe b)) -> WhenMissing f k x b)
-> (k -> x -> f (Maybe b)) -> WhenMissing f k x b
forall a b. (a -> b) -> a -> b
$ \k
k x
x -> do
Maybe a
res1 <- WhenMissing f k x a -> k -> x -> f (Maybe a)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k x a
m k
k x
x
case Maybe a
res1 of
Maybe a
Nothing -> Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure Maybe b
forall a. Maybe a
Nothing
Just a
r -> WhenMissing f k x b -> k -> x -> f (Maybe b)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey (a -> WhenMissing f k x b
f a
r) k
k x
x
{-# INLINE (>>=) #-}
mapWhenMissing :: (Applicative f, Monad f)
=> (a -> b)
-> WhenMissing f k x a -> WhenMissing f k x b
mapWhenMissing :: (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b
mapWhenMissing a -> b
f WhenMissing f k x a
t = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k b)
missingSubtree = \Map k x
m -> WhenMissing f k x a -> Map k x -> f (Map k a)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> Map k x -> f (Map k y)
missingSubtree WhenMissing f k x a
t Map k x
m f (Map k a) -> (Map k a -> f (Map k b)) -> f (Map k b)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
Evidence bound by a type signature of the constraint type Monad f
>>= \Map k a
m' -> Map k b -> f (Map k b)
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (m :: * -> *). Monad m => Applicative m
Evidence bound by a type signature of the constraint type Monad f
pure (Map k b -> f (Map k b)) -> Map k b -> f (Map k b)
forall a b. (a -> b) -> a -> b
$! (a -> b) -> Map k a -> Map k b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type forall k. Functor (Map k)
fmap a -> b
f Map k a
m'
, missingKey :: k -> x -> f (Maybe b)
missingKey = \k
k x
x -> WhenMissing f k x a -> k -> x -> f (Maybe a)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k x a
t k
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
Evidence bound by a type signature of the constraint type Monad f
>>= \Maybe a
q -> (Maybe b -> f (Maybe b)
forall (f :: * -> *) a. Applicative f => a -> f a
External instance of the constraint type forall (m :: * -> *). Monad m => Applicative m
Evidence bound by a type signature of the constraint type Monad f
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
External instance of the constraint type Functor Maybe
fmap a -> b
f Maybe a
q) }
{-# INLINE mapWhenMissing #-}
mapGentlyWhenMissing :: Functor f
=> (a -> b)
-> WhenMissing f k x a -> WhenMissing f k x b
mapGentlyWhenMissing :: (a -> b) -> WhenMissing f k x a -> WhenMissing f k x b
mapGentlyWhenMissing a -> b
f WhenMissing f k x a
t = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k b)
missingSubtree = \Map k x
m -> (a -> b) -> Map k a -> Map k b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type forall k. Functor (Map k)
fmap a -> b
f (Map k a -> Map k b) -> f (Map k a) -> f (Map k b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Evidence bound by a type signature of the constraint type Functor f
<$> WhenMissing f k x a -> Map k x -> f (Map k a)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> Map k x -> f (Map k y)
missingSubtree WhenMissing f k x a
t Map k x
m
, missingKey :: k -> x -> f (Maybe b)
missingKey = \k
k x
x -> (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
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
Evidence bound by a type signature of the constraint type Functor f
<$> WhenMissing f k x a -> k -> x -> f (Maybe a)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k x a
t k
k x
x }
{-# INLINE mapGentlyWhenMissing #-}
mapGentlyWhenMatched :: Functor f
=> (a -> b)
-> WhenMatched f k x y a -> WhenMatched f k x y b
mapGentlyWhenMatched :: (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b
mapGentlyWhenMatched a -> b
f WhenMatched f k x y a
t = (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall k x y (f :: * -> *) z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
zipWithMaybeAMatched ((k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b)
-> (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall a b. (a -> b) -> a -> b
$
\k
k x
x y
y -> (a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
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
Evidence bound by a type signature of the constraint type Functor f
<$> WhenMatched f k x y a -> k -> x -> y -> f (Maybe a)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k x y a
t k
k x
x y
y
{-# INLINE mapGentlyWhenMatched #-}
lmapWhenMissing :: (b -> a) -> WhenMissing f k a x -> WhenMissing f k b x
lmapWhenMissing :: (b -> a) -> WhenMissing f k a x -> WhenMissing f k b x
lmapWhenMissing b -> a
f WhenMissing f k a x
t = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k b -> f (Map k x)
missingSubtree = \Map k b
m -> WhenMissing f k a x -> Map k a -> f (Map k x)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> Map k x -> f (Map k y)
missingSubtree WhenMissing f k a x
t ((b -> a) -> Map k b -> Map k a
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
Instance of class: Functor of the constraint type forall k. Functor (Map k)
fmap b -> a
f Map k b
m)
, missingKey :: k -> b -> f (Maybe x)
missingKey = \k
k b
x -> WhenMissing f k a x -> k -> a -> f (Maybe x)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey WhenMissing f k a x
t k
k (b -> a
f b
x) }
{-# INLINE lmapWhenMissing #-}
contramapFirstWhenMatched :: (b -> a)
-> WhenMatched f k a y z
-> WhenMatched f k b y z
contramapFirstWhenMatched :: (b -> a) -> WhenMatched f k a y z -> WhenMatched f k b y z
contramapFirstWhenMatched b -> a
f WhenMatched f k a y z
t = (k -> b -> y -> f (Maybe z)) -> WhenMatched f k b y z
forall (f :: * -> *) k x y z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
WhenMatched ((k -> b -> y -> f (Maybe z)) -> WhenMatched f k b y z)
-> (k -> b -> y -> f (Maybe z)) -> WhenMatched f k b y z
forall a b. (a -> b) -> a -> b
$
\k
k b
x y
y -> WhenMatched f k a y z -> k -> a -> y -> f (Maybe z)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k a y z
t k
k (b -> a
f b
x) y
y
{-# INLINE contramapFirstWhenMatched #-}
contramapSecondWhenMatched :: (b -> a)
-> WhenMatched f k x a z
-> WhenMatched f k x b z
contramapSecondWhenMatched :: (b -> a) -> WhenMatched f k x a z -> WhenMatched f k x b z
contramapSecondWhenMatched b -> a
f WhenMatched f k x a z
t = (k -> x -> b -> f (Maybe z)) -> WhenMatched f k x b z
forall (f :: * -> *) k x y z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
WhenMatched ((k -> x -> b -> f (Maybe z)) -> WhenMatched f k x b z)
-> (k -> x -> b -> f (Maybe z)) -> WhenMatched f k x b z
forall a b. (a -> b) -> a -> b
$
\k
k x
x b
y -> WhenMatched f k x a z -> k -> x -> a -> f (Maybe z)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k x a z
t k
k x
x (b -> a
f b
y)
{-# INLINE contramapSecondWhenMatched #-}
type SimpleWhenMissing = WhenMissing Identity
newtype WhenMatched f k x y z = WhenMatched
{ WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
matchedKey :: k -> x -> y -> f (Maybe z) }
runWhenMatched :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched :: WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched = WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
matchedKey
{-# INLINE runWhenMatched #-}
runWhenMissing :: WhenMissing f k x y -> k -> x -> f (Maybe y)
runWhenMissing :: WhenMissing f k x y -> k -> x -> f (Maybe y)
runWhenMissing = WhenMissing f k x y -> k -> x -> f (Maybe y)
forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey
{-# INLINE runWhenMissing #-}
instance Functor f => Functor (WhenMatched f k x y) where
fmap :: (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b
fmap = (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b
forall (f :: * -> *) a b k x y.
Functor f =>
(a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b
Evidence bound by a type signature of the constraint type Functor f
mapWhenMatched
{-# INLINE fmap #-}
instance (Monad f, Applicative f) => Category.Category (WhenMatched f k x) where
id :: WhenMatched f k x a a
id = (k -> x -> a -> a) -> WhenMatched f k x a a
forall (f :: * -> *) k x y z.
Applicative f =>
(k -> x -> y -> z) -> WhenMatched f k x y z
Evidence bound by a type signature of the constraint type Applicative f
zipWithMatched (\k
_ x
_ a
y -> a
y)
WhenMatched f k x b c
f . :: WhenMatched f k x b c
-> WhenMatched f k x a b -> WhenMatched f k x a c
. WhenMatched f k x a b
g = (k -> x -> a -> f (Maybe c)) -> WhenMatched f k x a c
forall k x y (f :: * -> *) z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
zipWithMaybeAMatched ((k -> x -> a -> f (Maybe c)) -> WhenMatched f k x a c)
-> (k -> x -> a -> f (Maybe c)) -> WhenMatched f k x a c
forall a b. (a -> b) -> a -> b
$
\k
k x
x a
y -> do
Maybe b
res <- WhenMatched f k x a b -> k -> x -> a -> f (Maybe b)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k x a b
g k
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
Evidence bound by a type signature of the constraint type Applicative f
pure Maybe c
forall a. Maybe a
Nothing
Just b
r -> WhenMatched f k x b c -> k -> x -> b -> f (Maybe c)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k x b c
f k
k x
x b
r
{-# INLINE id #-}
{-# INLINE (.) #-}
instance (Monad f, Applicative f) => Applicative (WhenMatched f k x y) where
pure :: a -> WhenMatched f k x y a
pure a
x = (k -> x -> y -> a) -> WhenMatched f k x y a
forall (f :: * -> *) k x y z.
Applicative f =>
(k -> x -> y -> z) -> WhenMatched f k x y z
Evidence bound by a type signature of the constraint type Applicative f
zipWithMatched (\k
_ x
_ y
_ -> a
x)
WhenMatched f k x y (a -> b)
fs <*> :: WhenMatched f k x y (a -> b)
-> WhenMatched f k x y a -> WhenMatched f k x y b
<*> WhenMatched f k x y a
xs = (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall k x y (f :: * -> *) z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
zipWithMaybeAMatched ((k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b)
-> (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall a b. (a -> b) -> a -> b
$ \k
k x
x y
y -> do
Maybe (a -> b)
res <- WhenMatched f k x y (a -> b) -> k -> x -> y -> f (Maybe (a -> b))
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k x y (a -> b)
fs k
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
Evidence bound by a type signature of the constraint type Applicative f
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
Evidence bound by a type signature of the constraint type Applicative f
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
External instance of the constraint type Functor Maybe
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
Evidence bound by a type signature of the constraint type Monad f
=<< WhenMatched f k x y a -> k -> x -> y -> f (Maybe a)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k x y a
xs k
k x
x y
y
{-# INLINE pure #-}
{-# INLINE (<*>) #-}
instance (Monad f, Applicative f) => Monad (WhenMatched f k x y) where
#if !MIN_VERSION_base(4,8,0)
return = pure
#endif
WhenMatched f k x y a
m >>= :: WhenMatched f k x y a
-> (a -> WhenMatched f k x y b) -> WhenMatched f k x y b
>>= a -> WhenMatched f k x y b
f = (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall k x y (f :: * -> *) z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
zipWithMaybeAMatched ((k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b)
-> (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall a b. (a -> b) -> a -> b
$ \k
k x
x y
y -> do
Maybe a
res <- WhenMatched f k x y a -> k -> x -> y -> f (Maybe a)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched WhenMatched f k x y a
m k
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
Evidence bound by a type signature of the constraint type Applicative f
pure Maybe b
forall a. Maybe a
Nothing
Just a
r -> WhenMatched f k x y b -> k -> x -> y -> f (Maybe b)
forall (f :: * -> *) k x y z.
WhenMatched f k x y z -> k -> x -> y -> f (Maybe z)
runWhenMatched (a -> WhenMatched f k x y b
f a
r) k
k x
x y
y
{-# INLINE (>>=) #-}
mapWhenMatched :: Functor f
=> (a -> b)
-> WhenMatched f k x y a
-> WhenMatched f k x y b
mapWhenMatched :: (a -> b) -> WhenMatched f k x y a -> WhenMatched f k x y b
mapWhenMatched a -> b
f (WhenMatched k -> x -> y -> f (Maybe a)
g) = (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall (f :: * -> *) k x y z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
WhenMatched ((k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b)
-> (k -> x -> y -> f (Maybe b)) -> WhenMatched f k x y b
forall a b. (a -> b) -> a -> b
$ \k
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
Evidence bound by a type signature of the constraint type Functor f
fmap ((a -> b) -> Maybe a -> Maybe b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type Functor Maybe
fmap a -> b
f) (k -> x -> y -> f (Maybe a)
g k
k x
x y
y)
{-# INLINE mapWhenMatched #-}
type SimpleWhenMatched = WhenMatched Identity
zipWithMatched :: Applicative f
=> (k -> x -> y -> z)
-> WhenMatched f k x y z
zipWithMatched :: (k -> x -> y -> z) -> WhenMatched f k x y z
zipWithMatched k -> x -> y -> z
f = (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall (f :: * -> *) k x y z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
WhenMatched ((k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z)
-> (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall a b. (a -> b) -> a -> b
$ \ k
k x
x y
y -> Maybe z -> f (Maybe z)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
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
$ k -> x -> y -> z
f k
k x
x y
y
{-# INLINE zipWithMatched #-}
zipWithAMatched :: Applicative f
=> (k -> x -> y -> f z)
-> WhenMatched f k x y z
zipWithAMatched :: (k -> x -> y -> f z) -> WhenMatched f k x y z
zipWithAMatched k -> x -> y -> f z
f = (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall (f :: * -> *) k x y z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
WhenMatched ((k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z)
-> (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall a b. (a -> b) -> a -> b
$ \ k
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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
<$> k -> x -> y -> f z
f k
k x
x y
y
{-# INLINE zipWithAMatched #-}
zipWithMaybeMatched :: Applicative f
=> (k -> x -> y -> Maybe z)
-> WhenMatched f k x y z
zipWithMaybeMatched :: (k -> x -> y -> Maybe z) -> WhenMatched f k x y z
zipWithMaybeMatched k -> x -> y -> Maybe z
f = (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall (f :: * -> *) k x y z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
WhenMatched ((k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z)
-> (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall a b. (a -> b) -> a -> b
$ \ k
k x
x y
y -> Maybe z -> f (Maybe z)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Maybe z -> f (Maybe z)) -> Maybe z -> f (Maybe z)
forall a b. (a -> b) -> a -> b
$ k -> x -> y -> Maybe z
f k
k x
x y
y
{-# INLINE zipWithMaybeMatched #-}
zipWithMaybeAMatched :: (k -> x -> y -> f (Maybe z))
-> WhenMatched f k x y z
zipWithMaybeAMatched :: (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
zipWithMaybeAMatched k -> x -> y -> f (Maybe z)
f = (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall (f :: * -> *) k x y z.
(k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
WhenMatched ((k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z)
-> (k -> x -> y -> f (Maybe z)) -> WhenMatched f k x y z
forall a b. (a -> b) -> a -> b
$ \ k
k x
x y
y -> k -> x -> y -> f (Maybe z)
f k
k x
x y
y
{-# INLINE zipWithMaybeAMatched #-}
dropMissing :: Applicative f => WhenMissing f k x y
dropMissing :: WhenMissing f k x y
dropMissing = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k y)
missingSubtree = f (Map k y) -> Map k x -> f (Map k y)
forall a b. a -> b -> a
const (Map k y -> f (Map k y)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure Map k y
forall k a. Map k a
Tip)
, missingKey :: k -> x -> f (Maybe y)
missingKey = \k
_ x
_ -> Maybe y -> f (Maybe y)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure Maybe y
forall a. Maybe a
Nothing }
{-# INLINE dropMissing #-}
preserveMissing :: Applicative f => WhenMissing f k x x
preserveMissing :: WhenMissing f k x x
preserveMissing = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k x)
missingSubtree = Map k x -> f (Map k x)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure
, missingKey :: k -> x -> f (Maybe x)
missingKey = \k
_ x
v -> Maybe x -> f (Maybe x)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (x -> Maybe x
forall a. a -> Maybe a
Just x
v) }
{-# INLINE preserveMissing #-}
preserveMissing' :: Applicative f => WhenMissing f k x x
preserveMissing' :: WhenMissing f k x x
preserveMissing' = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k x)
missingSubtree = \Map k x
t -> Map k x -> f (Map k x)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Map k x -> f (Map k x)) -> Map k x -> f (Map k x)
forall a b. (a -> b) -> a -> b
$! Map k x -> ()
forall k a. Map k a -> ()
forceTree Map k x
t () -> Map k x -> Map k x
`seq` Map k x
t
, missingKey :: k -> x -> f (Maybe x)
missingKey = \k
_ x
v -> Maybe x -> f (Maybe x)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Maybe x -> f (Maybe x)) -> Maybe x -> f (Maybe x)
forall a b. (a -> b) -> a -> b
$! x -> Maybe x
forall a. a -> Maybe a
Just (x -> Maybe x) -> x -> Maybe x
forall a b. (a -> b) -> a -> b
$! x
v }
{-# INLINE preserveMissing' #-}
forceTree :: Map k a -> ()
forceTree :: Map k a -> ()
forceTree (Bin Int
_ k
_ a
v Map k a
l Map k a
r) = a
v a -> () -> ()
`seq` Map k a -> ()
forall k a. Map k a -> ()
forceTree Map k a
l () -> () -> ()
`seq` Map k a -> ()
forall k a. Map k a -> ()
forceTree Map k a
r () -> () -> ()
`seq` ()
forceTree Map k a
Tip = ()
mapMissing :: Applicative f => (k -> x -> y) -> WhenMissing f k x y
mapMissing :: (k -> x -> y) -> WhenMissing f k x y
mapMissing k -> x -> y
f = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k y)
missingSubtree = \Map k x
m -> Map k y -> f (Map k y)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Map k y -> f (Map k y)) -> Map k y -> f (Map k y)
forall a b. (a -> b) -> a -> b
$! (k -> x -> y) -> Map k x -> Map k y
forall k a b. (k -> a -> b) -> Map k a -> Map k b
mapWithKey k -> x -> y
f Map k x
m
, missingKey :: k -> x -> f (Maybe y)
missingKey = \ k
k x
x -> Maybe y -> f (Maybe y)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
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 (k -> x -> y
f k
k x
x) }
{-# INLINE mapMissing #-}
mapMaybeMissing :: Applicative f => (k -> x -> Maybe y) -> WhenMissing f k x y
mapMaybeMissing :: (k -> x -> Maybe y) -> WhenMissing f k x y
mapMaybeMissing k -> x -> Maybe y
f = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k y)
missingSubtree = \Map k x
m -> Map k y -> f (Map k y)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Map k y -> f (Map k y)) -> Map k y -> f (Map k y)
forall a b. (a -> b) -> a -> b
$! (k -> x -> Maybe y) -> Map k x -> Map k y
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey k -> x -> Maybe y
f Map k x
m
, missingKey :: k -> x -> f (Maybe y)
missingKey = \k
k x
x -> Maybe y -> f (Maybe y)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Maybe y -> f (Maybe y)) -> Maybe y -> f (Maybe y)
forall a b. (a -> b) -> a -> b
$! k -> x -> Maybe y
f k
k x
x }
{-# INLINE mapMaybeMissing #-}
filterMissing :: Applicative f
=> (k -> x -> Bool) -> WhenMissing f k x x
filterMissing :: (k -> x -> Bool) -> WhenMissing f k x x
filterMissing k -> x -> Bool
f = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k x)
missingSubtree = \Map k x
m -> Map k x -> f (Map k x)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Map k x -> f (Map k x)) -> Map k x -> f (Map k x)
forall a b. (a -> b) -> a -> b
$! (k -> x -> Bool) -> Map k x -> Map k x
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
filterWithKey k -> x -> Bool
f Map k x
m
, missingKey :: k -> x -> f (Maybe x)
missingKey = \k
k x
x -> Maybe x -> f (Maybe x)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure (Maybe x -> f (Maybe x)) -> Maybe x -> f (Maybe x)
forall a b. (a -> b) -> a -> b
$! if k -> x -> Bool
f k
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
=> (k -> x -> f Bool) -> WhenMissing f k x x
filterAMissing :: (k -> x -> f Bool) -> WhenMissing f k x x
filterAMissing k -> x -> f Bool
f = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k x)
missingSubtree = \Map k x
m -> (k -> x -> f Bool) -> Map k x -> f (Map k x)
forall (f :: * -> *) k a.
Applicative f =>
(k -> a -> f Bool) -> Map k a -> f (Map k a)
Evidence bound by a type signature of the constraint type Applicative f
filterWithKeyA k -> x -> f Bool
f Map k x
m
, missingKey :: k -> x -> f (Maybe x)
missingKey = \k
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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
<$> k -> x -> f Bool
f k
k x
x }
{-# INLINE filterAMissing #-}
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
=> (k -> x -> f y) -> WhenMissing f k x y
traverseMissing :: (k -> x -> f y) -> WhenMissing f k x y
traverseMissing k -> x -> f y
f = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k y)
missingSubtree = (k -> x -> f y) -> Map k x -> f (Map k y)
forall (t :: * -> *) k a b.
Applicative t =>
(k -> a -> t b) -> Map k a -> t (Map k b)
Evidence bound by a type signature of the constraint type Applicative f
traverseWithKey k -> x -> f y
f
, missingKey :: k -> x -> f (Maybe y)
missingKey = \k
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
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
<$> k -> x -> f y
f k
k x
x }
{-# INLINE traverseMissing #-}
traverseMaybeMissing :: Applicative f
=> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
traverseMaybeMissing :: (k -> x -> f (Maybe y)) -> WhenMissing f k x y
traverseMaybeMissing k -> x -> f (Maybe y)
f = WhenMissing :: forall (f :: * -> *) k x y.
(Map k x -> f (Map k y))
-> (k -> x -> f (Maybe y)) -> WhenMissing f k x y
WhenMissing
{ missingSubtree :: Map k x -> f (Map k y)
missingSubtree = (k -> x -> f (Maybe y)) -> Map k x -> f (Map k y)
forall (f :: * -> *) k a b.
Applicative f =>
(k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
Evidence bound by a type signature of the constraint type Applicative f
traverseMaybeWithKey k -> x -> f (Maybe y)
f
, missingKey :: k -> x -> f (Maybe y)
missingKey = k -> x -> f (Maybe y)
f }
{-# INLINE traverseMaybeMissing #-}
merge :: Ord k
=> SimpleWhenMissing k a c
-> SimpleWhenMissing k b c
-> SimpleWhenMatched k a b c
-> Map k a
-> Map k b
-> Map k c
merge :: SimpleWhenMissing k a c
-> SimpleWhenMissing k b c
-> SimpleWhenMatched k a b c
-> Map k a
-> Map k b
-> Map k c
merge SimpleWhenMissing k a c
g1 SimpleWhenMissing k b c
g2 SimpleWhenMatched k a b c
f Map k a
m1 Map k b
m2 = Identity (Map k c) -> Map k c
forall a. Identity a -> a
runIdentity (Identity (Map k c) -> Map k c) -> Identity (Map k c) -> Map k c
forall a b. (a -> b) -> a -> b
$
SimpleWhenMissing k a c
-> SimpleWhenMissing k b c
-> SimpleWhenMatched k a b c
-> Map k a
-> Map k b
-> Identity (Map k c)
forall (f :: * -> *) k a c b.
(Applicative f, Ord k) =>
WhenMissing f k a c
-> WhenMissing f k b c
-> WhenMatched f k a b c
-> Map k a
-> Map k b
-> f (Map k c)
Evidence bound by a type signature of the constraint type Ord k
External instance of the constraint type Applicative Identity
mergeA SimpleWhenMissing k a c
g1 SimpleWhenMissing k b c
g2 SimpleWhenMatched k a b c
f Map k a
m1 Map k b
m2
{-# INLINE merge #-}
mergeA
:: (Applicative f, Ord k)
=> WhenMissing f k a c
-> WhenMissing f k b c
-> WhenMatched f k a b c
-> Map k a
-> Map k b
-> f (Map k c)
mergeA :: WhenMissing f k a c
-> WhenMissing f k b c
-> WhenMatched f k a b c
-> Map k a
-> Map k b
-> f (Map k c)
mergeA
WhenMissing{missingSubtree :: forall (f :: * -> *) k x y.
WhenMissing f k x y -> Map k x -> f (Map k y)
missingSubtree = Map k a -> f (Map k c)
g1t, missingKey :: forall (f :: * -> *) k x y.
WhenMissing f k x y -> k -> x -> f (Maybe y)
missingKey = k -> a -> f (Maybe c)
g1k}
WhenMissing{missingSubtree :: forall (f :: * -> *) k x y.
WhenMissing f k x y -> Map k x -> f (Map k y)
missingSubtree = Map k b -> f (Map k c)
g2t}
(WhenMatched k -> a -> b -> f (Maybe c)
f) = Map k a -> Map k b -> f (Map k c)
go
where
go :: Map k a -> Map k b -> f (Map k c)
go Map k a
t1 Map k b
Tip = Map k a -> f (Map k c)
g1t Map k a
t1
go Map k a
Tip Map k b
t2 = Map k b -> f (Map k c)
g2t Map k b
t2
go (Bin Int
_ k
kx a
x1 Map k a
l1 Map k a
r1) Map k b
t2 = case k -> Map k b -> (Map k b, Maybe b, Map k b)
forall k a. Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitLookup k
kx Map k b
t2 of
(Map k b
l2, Maybe b
mx2, Map k b
r2) -> case Maybe b
mx2 of
Maybe b
Nothing -> (Map k c -> Maybe c -> Map k c -> Map k c)
-> f (Map k c) -> f (Maybe c) -> f (Map k c) -> f (Map k c)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
Evidence bound by a type signature of the constraint type Applicative f
liftA3 (\Map k c
l' Maybe c
mx' Map k c
r' -> (Map k c -> Map k c -> Map k c)
-> (c -> Map k c -> Map k c -> Map k c)
-> Maybe c
-> Map k c
-> Map k c
-> Map k c
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Map k c -> Map k c -> Map k c
forall k a. Map k a -> Map k a -> Map k a
link2 (k -> c -> Map k c -> Map k c -> Map k c
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx) Maybe c
mx' Map k c
l' Map k c
r')
f (Map k c)
l1l2 (k -> a -> f (Maybe c)
g1k k
kx a
x1) f (Map k c)
r1r2
Just b
x2 -> (Map k c -> Maybe c -> Map k c -> Map k c)
-> f (Map k c) -> f (Maybe c) -> f (Map k c) -> f (Map k c)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
Evidence bound by a type signature of the constraint type Applicative f
liftA3 (\Map k c
l' Maybe c
mx' Map k c
r' -> (Map k c -> Map k c -> Map k c)
-> (c -> Map k c -> Map k c -> Map k c)
-> Maybe c
-> Map k c
-> Map k c
-> Map k c
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Map k c -> Map k c -> Map k c
forall k a. Map k a -> Map k a -> Map k a
link2 (k -> c -> Map k c -> Map k c -> Map k c
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx) Maybe c
mx' Map k c
l' Map k c
r')
f (Map k c)
l1l2 (k -> a -> b -> f (Maybe c)
f k
kx a
x1 b
x2) f (Map k c)
r1r2
where
!l1l2 :: f (Map k c)
l1l2 = Map k a -> Map k b -> f (Map k c)
go Map k a
l1 Map k b
l2
!r1r2 :: f (Map k c)
r1r2 = Map k a -> Map k b -> f (Map k c)
go Map k a
r1 Map k b
r2
{-# INLINE mergeA #-}
mergeWithKey :: Ord k
=> (k -> a -> b -> Maybe c)
-> (Map k a -> Map k c)
-> (Map k b -> Map k c)
-> Map k a -> Map k b -> Map k c
mergeWithKey :: (k -> a -> b -> Maybe c)
-> (Map k a -> Map k c)
-> (Map k b -> Map k c)
-> Map k a
-> Map k b
-> Map k c
mergeWithKey k -> a -> b -> Maybe c
f Map k a -> Map k c
g1 Map k b -> Map k c
g2 = Map k a -> Map k b -> Map k c
go
where
go :: Map k a -> Map k b -> Map k c
go Map k a
Tip Map k b
t2 = Map k b -> Map k c
g2 Map k b
t2
go Map k a
t1 Map k b
Tip = Map k a -> Map k c
g1 Map k a
t1
go (Bin Int
_ k
kx a
x Map k a
l1 Map k a
r1) Map k b
t2 =
case Maybe b
found of
Maybe b
Nothing -> case Map k a -> Map k c
g1 (k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x) of
Map k c
Tip -> Map k c -> Map k c -> Map k c
forall k a. Map k a -> Map k a -> Map k a
link2 Map k c
l' Map k c
r'
(Bin Int
_ k
_ c
x' Map k c
Tip Map k c
Tip) -> k -> c -> Map k c -> Map k c -> Map k c
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx c
x' Map k c
l' Map k c
r'
Map k c
_ -> [Char] -> Map k c
forall a. HasCallStack => [Char] -> a
error [Char]
"mergeWithKey: Given function only1 does not fulfill required conditions (see documentation)"
Just b
x2 -> case k -> a -> b -> Maybe c
f k
kx a
x b
x2 of
Maybe c
Nothing -> Map k c -> Map k c -> Map k c
forall k a. Map k a -> Map k a -> Map k a
link2 Map k c
l' Map k c
r'
Just c
x' -> k -> c -> Map k c -> Map k c -> Map k c
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx c
x' Map k c
l' Map k c
r'
where
(Map k b
l2, Maybe b
found, Map k b
r2) = k -> Map k b -> (Map k b, Maybe b, Map k b)
forall k a. Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a)
Evidence bound by a type signature of the constraint type Ord k
splitLookup k
kx Map k b
t2
l' :: Map k c
l' = Map k a -> Map k b -> Map k c
go Map k a
l1 Map k b
l2
r' :: Map k c
r' = Map k a -> Map k b -> Map k c
go Map k a
r1 Map k b
r2
{-# INLINE mergeWithKey #-}
isSubmapOf :: (Ord k,Eq a) => Map k a -> Map k a -> Bool
isSubmapOf :: Map k a -> Map k a -> Bool
isSubmapOf Map k a
m1 Map k a
m2 = (a -> a -> Bool) -> Map k a -> Map k a -> Bool
forall k a b.
Ord k =>
(a -> b -> Bool) -> Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord k
isSubmapOfBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
(==) Map k a
m1 Map k a
m2
#if __GLASGOW_HASKELL__
{-# INLINABLE isSubmapOf #-}
#endif
isSubmapOfBy :: Ord k => (a->b->Bool) -> Map k a -> Map k b -> Bool
isSubmapOfBy :: (a -> b -> Bool) -> Map k a -> Map k b -> Bool
isSubmapOfBy a -> b -> Bool
f Map k a
t1 Map k b
t2
= Map k a -> Int
forall k a. Map k a -> Int
size Map k a
t1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Map k b -> Int
forall k a. Map k a -> Int
size Map k b
t2 Bool -> Bool -> Bool
&& (a -> b -> Bool) -> Map k a -> Map k b -> Bool
forall k a b.
Ord k =>
(a -> b -> Bool) -> Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord k
submap' a -> b -> Bool
f Map k a
t1 Map k b
t2
#if __GLASGOW_HASKELL__
{-# INLINABLE isSubmapOfBy #-}
#endif
submap' :: Ord a => (b -> c -> Bool) -> Map a b -> Map a c -> Bool
submap' :: (b -> c -> Bool) -> Map a b -> Map a c -> Bool
submap' b -> c -> Bool
_ Map a b
Tip Map a c
_ = Bool
True
submap' b -> c -> Bool
_ Map a b
_ Map a c
Tip = Bool
False
submap' b -> c -> Bool
f (Bin Int
1 a
kx b
x Map a b
_ Map a b
_) Map a c
t
= case a -> Map a c -> Maybe c
forall k a. Ord k => k -> Map k a -> Maybe a
Evidence bound by a type signature of the constraint type Ord a
lookup a
kx Map a c
t of
Just c
y -> b -> c -> Bool
f b
x c
y
Maybe c
Nothing -> Bool
False
submap' b -> c -> Bool
f (Bin Int
_ a
kx b
x Map a b
l Map a b
r) Map a c
t
= case Maybe c
found of
Maybe c
Nothing -> Bool
False
Just c
y -> b -> c -> Bool
f b
x c
y
Bool -> Bool -> Bool
&& Map a b -> Int
forall k a. Map k a -> Int
size Map a b
l Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Map a c -> Int
forall k a. Map k a -> Int
size Map a c
lt Bool -> Bool -> Bool
&& Map a b -> Int
forall k a. Map k a -> Int
size Map a b
r Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
<= Map a c -> Int
forall k a. Map k a -> Int
size Map a c
gt
Bool -> Bool -> Bool
&& (b -> c -> Bool) -> Map a b -> Map a c -> Bool
forall k a b.
Ord k =>
(a -> b -> Bool) -> Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord a
submap' b -> c -> Bool
f Map a b
l Map a c
lt Bool -> Bool -> Bool
&& (b -> c -> Bool) -> Map a b -> Map a c -> Bool
forall k a b.
Ord k =>
(a -> b -> Bool) -> Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord a
submap' b -> c -> Bool
f Map a b
r Map a c
gt
where
(Map a c
lt,Maybe c
found,Map a c
gt) = a -> Map a c -> (Map a c, Maybe c, Map a c)
forall k a. Ord k => k -> Map k a -> (Map k a, Maybe a, Map k a)
Evidence bound by a type signature of the constraint type Ord a
splitLookup a
kx Map a c
t
#if __GLASGOW_HASKELL__
{-# INLINABLE submap' #-}
#endif
isProperSubmapOf :: (Ord k,Eq a) => Map k a -> Map k a -> Bool
isProperSubmapOf :: Map k a -> Map k a -> Bool
isProperSubmapOf Map k a
m1 Map k a
m2
= (a -> a -> Bool) -> Map k a -> Map k a -> Bool
forall k a b.
Ord k =>
(a -> b -> Bool) -> Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord k
isProperSubmapOfBy a -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
(==) Map k a
m1 Map k a
m2
#if __GLASGOW_HASKELL__
{-# INLINABLE isProperSubmapOf #-}
#endif
isProperSubmapOfBy :: Ord k => (a -> b -> Bool) -> Map k a -> Map k b -> Bool
isProperSubmapOfBy :: (a -> b -> Bool) -> Map k a -> Map k b -> Bool
isProperSubmapOfBy a -> b -> Bool
f Map k a
t1 Map k b
t2
= Map k a -> Int
forall k a. Map k a -> Int
size Map k a
t1 Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Map k b -> Int
forall k a. Map k a -> Int
size Map k b
t2 Bool -> Bool -> Bool
&& (a -> b -> Bool) -> Map k a -> Map k b -> Bool
forall k a b.
Ord k =>
(a -> b -> Bool) -> Map k a -> Map k b -> Bool
Evidence bound by a type signature of the constraint type Ord k
submap' a -> b -> Bool
f Map k a
t1 Map k b
t2
#if __GLASGOW_HASKELL__
{-# INLINABLE isProperSubmapOfBy #-}
#endif
filter :: (a -> Bool) -> Map k a -> Map k a
filter :: (a -> Bool) -> Map k a -> Map k a
filter a -> Bool
p Map k a
m
= (k -> a -> Bool) -> Map k a -> Map k a
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
filterWithKey (\k
_ a
x -> a -> Bool
p a
x) Map k a
m
filterWithKey :: (k -> a -> Bool) -> Map k a -> Map k a
filterWithKey :: (k -> a -> Bool) -> Map k a -> Map k a
filterWithKey k -> a -> Bool
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
filterWithKey k -> a -> Bool
p t :: Map k a
t@(Bin Int
_ k
kx a
x Map k a
l Map k a
r)
| k -> a -> Bool
p k
kx a
x = if Map k a
pl Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l Bool -> Bool -> Bool
&& Map k a
pr Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r
then Map k a
t
else k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
pl Map k a
pr
| Bool
otherwise = Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
pl Map k a
pr
where !pl :: Map k a
pl = (k -> a -> Bool) -> Map k a -> Map k a
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
filterWithKey k -> a -> Bool
p Map k a
l
!pr :: Map k a
pr = (k -> a -> Bool) -> Map k a -> Map k a
forall k a. (k -> a -> Bool) -> Map k a -> Map k a
filterWithKey k -> a -> Bool
p Map k a
r
filterWithKeyA :: Applicative f => (k -> a -> f Bool) -> Map k a -> f (Map k a)
filterWithKeyA :: (k -> a -> f Bool) -> Map k a -> f (Map k a)
filterWithKeyA k -> a -> f Bool
_ Map k a
Tip = Map k a -> f (Map k a)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure Map k a
forall k a. Map k a
Tip
filterWithKeyA k -> a -> f Bool
p t :: Map k a
t@(Bin Int
_ k
kx a
x Map k a
l Map k a
r) =
(Bool -> Map k a -> Map k a -> Map k a)
-> f Bool -> f (Map k a) -> f (Map k a) -> f (Map k a)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
Evidence bound by a type signature of the constraint type Applicative f
liftA3 Bool -> Map k a -> Map k a -> Map k a
combine (k -> a -> f Bool
p k
kx a
x) ((k -> a -> f Bool) -> Map k a -> f (Map k a)
forall (f :: * -> *) k a.
Applicative f =>
(k -> a -> f Bool) -> Map k a -> f (Map k a)
Evidence bound by a type signature of the constraint type Applicative f
filterWithKeyA k -> a -> f Bool
p Map k a
l) ((k -> a -> f Bool) -> Map k a -> f (Map k a)
forall (f :: * -> *) k a.
Applicative f =>
(k -> a -> f Bool) -> Map k a -> f (Map k a)
Evidence bound by a type signature of the constraint type Applicative f
filterWithKeyA k -> a -> f Bool
p Map k a
r)
where
combine :: Bool -> Map k a -> Map k a -> Map k a
combine Bool
True Map k a
pl Map k a
pr
| Map k a
pl Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l Bool -> Bool -> Bool
&& Map k a
pr Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r = Map k a
t
| Bool
otherwise = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
pl Map k a
pr
combine Bool
False Map k a
pl Map k a
pr = Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
pl Map k a
pr
takeWhileAntitone :: (k -> Bool) -> Map k a -> Map k a
takeWhileAntitone :: (k -> Bool) -> Map k a -> Map k a
takeWhileAntitone k -> Bool
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
takeWhileAntitone k -> Bool
p (Bin Int
_ k
kx a
x Map k a
l Map k a
r)
| k -> Bool
p k
kx = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l ((k -> Bool) -> Map k a -> Map k a
forall k a. (k -> Bool) -> Map k a -> Map k a
takeWhileAntitone k -> Bool
p Map k a
r)
| Bool
otherwise = (k -> Bool) -> Map k a -> Map k a
forall k a. (k -> Bool) -> Map k a -> Map k a
takeWhileAntitone k -> Bool
p Map k a
l
dropWhileAntitone :: (k -> Bool) -> Map k a -> Map k a
dropWhileAntitone :: (k -> Bool) -> Map k a -> Map k a
dropWhileAntitone k -> Bool
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip
dropWhileAntitone k -> Bool
p (Bin Int
_ k
kx a
x Map k a
l Map k a
r)
| k -> Bool
p k
kx = (k -> Bool) -> Map k a -> Map k a
forall k a. (k -> Bool) -> Map k a -> Map k a
dropWhileAntitone k -> Bool
p Map k a
r
| Bool
otherwise = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x ((k -> Bool) -> Map k a -> Map k a
forall k a. (k -> Bool) -> Map k a -> Map k a
dropWhileAntitone k -> Bool
p Map k a
l) Map k a
r
spanAntitone :: (k -> Bool) -> Map k a -> (Map k a, Map k a)
spanAntitone :: (k -> Bool) -> Map k a -> (Map k a, Map k a)
spanAntitone k -> Bool
p0 Map k a
m = StrictPair (Map k a) (Map k a) -> (Map k a, Map k a)
forall a b. StrictPair a b -> (a, b)
toPair ((k -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
forall {k} {a}.
(k -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> Bool
p0 Map k a
m)
where
go :: (k -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> Bool
_ Map k a
Tip = Map k a
forall k a. Map k a
Tip Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
forall k a. Map k a
Tip
go k -> Bool
p (Bin Int
_ k
kx a
x Map k a
l Map k a
r)
| k -> Bool
p k
kx = let Map k a
u :*: Map k a
v = (k -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> Bool
p Map k a
r in k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
u Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
v
| Bool
otherwise = let Map k a
u :*: Map k a
v = (k -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> Bool
p Map k a
l in Map k a
u Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
v Map k a
r
partition :: (a -> Bool) -> Map k a -> (Map k a,Map k a)
partition :: (a -> Bool) -> Map k a -> (Map k a, Map k a)
partition a -> Bool
p Map k a
m
= (k -> a -> Bool) -> Map k a -> (Map k a, Map k a)
forall k a. (k -> a -> Bool) -> Map k a -> (Map k a, Map k a)
partitionWithKey (\k
_ a
x -> a -> Bool
p a
x) Map k a
m
partitionWithKey :: (k -> a -> Bool) -> Map k a -> (Map k a,Map k a)
partitionWithKey :: (k -> a -> Bool) -> Map k a -> (Map k a, Map k a)
partitionWithKey k -> a -> Bool
p0 Map k a
t0 = StrictPair (Map k a) (Map k a) -> (Map k a, Map k a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Map k a) (Map k a) -> (Map k a, Map k a))
-> StrictPair (Map k a) (Map k a) -> (Map k a, Map k a)
forall a b. (a -> b) -> a -> b
$ (k -> a -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
forall {k} {a}.
(k -> a -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> a -> Bool
p0 Map k a
t0
where
go :: (k -> a -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> a -> Bool
_ Map k a
Tip = (Map k a
forall k a. Map k a
Tip Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
forall k a. Map k a
Tip)
go k -> a -> Bool
p t :: Map k a
t@(Bin Int
_ k
kx a
x Map k a
l Map k a
r)
| k -> a -> Bool
p k
kx a
x = (if Map k a
l1 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l Bool -> Bool -> Bool
&& Map k a
r1 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r
then Map k a
t
else k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l1 Map k a
r1) Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l2 Map k a
r2
| Bool
otherwise = Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l1 Map k a
r1 Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*:
(if Map k a
l2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
l Bool -> Bool -> Bool
&& Map k a
r2 Map k a -> Map k a -> Bool
forall a. a -> a -> Bool
`ptrEq` Map k a
r
then Map k a
t
else k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l2 Map k a
r2)
where
(Map k a
l1 :*: Map k a
l2) = (k -> a -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> a -> Bool
p Map k a
l
(Map k a
r1 :*: Map k a
r2) = (k -> a -> Bool) -> Map k a -> StrictPair (Map k a) (Map k a)
go k -> a -> Bool
p Map k a
r
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b
mapMaybe :: (a -> Maybe b) -> Map k a -> Map k b
mapMaybe a -> Maybe b
f = (k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey (\k
_ a
x -> a -> Maybe b
f a
x)
mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey :: (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey k -> a -> Maybe b
_ Map k a
Tip = Map k b
forall k a. Map k a
Tip
mapMaybeWithKey k -> a -> Maybe b
f (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = case k -> a -> Maybe b
f k
kx a
x of
Just b
y -> k -> b -> Map k b -> Map k b -> Map k b
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx b
y ((k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey k -> a -> Maybe b
f Map k a
l) ((k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey k -> a -> Maybe b
f Map k a
r)
Maybe b
Nothing -> Map k b -> Map k b -> Map k b
forall k a. Map k a -> Map k a -> Map k a
link2 ((k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey k -> a -> Maybe b
f Map k a
l) ((k -> a -> Maybe b) -> Map k a -> Map k b
forall k a b. (k -> a -> Maybe b) -> Map k a -> Map k b
mapMaybeWithKey k -> a -> Maybe b
f Map k a
r)
traverseMaybeWithKey :: Applicative f
=> (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
traverseMaybeWithKey :: (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
traverseMaybeWithKey = (k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
forall (f :: * -> *) k a b.
Applicative f =>
(k -> a -> f (Maybe b)) -> Map k a -> f (Map k b)
Evidence bound by a type signature of the constraint type Applicative f
go
where
go :: (k -> t -> f (Maybe a)) -> Map k t -> f (Map k a)
go k -> t -> f (Maybe a)
_ Map k t
Tip = Map k a -> f (Map k a)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative f
pure Map k a
forall k a. Map k a
Tip
go k -> t -> f (Maybe a)
f (Bin Int
_ k
kx t
x Map k t
Tip Map k t
Tip) = Map k a -> (a -> Map k a) -> Maybe a -> Map k a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe Map k a
forall k a. Map k a
Tip (\a
x' -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx a
x' Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) (Maybe a -> Map k a) -> f (Maybe a) -> f (Map k a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative f
<$> k -> t -> f (Maybe a)
f k
kx t
x
go k -> t -> f (Maybe a)
f (Bin Int
_ k
kx t
x Map k t
l Map k t
r) = (Map k a -> Maybe a -> Map k a -> Map k a)
-> f (Map k a) -> f (Maybe a) -> f (Map k a) -> f (Map k a)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
Evidence bound by a type signature of the constraint type Applicative f
liftA3 Map k a -> Maybe a -> Map k a -> Map k a
combine ((k -> t -> f (Maybe a)) -> Map k t -> f (Map k a)
go k -> t -> f (Maybe a)
f Map k t
l) (k -> t -> f (Maybe a)
f k
kx t
x) ((k -> t -> f (Maybe a)) -> Map k t -> f (Map k a)
go k -> t -> f (Maybe a)
f Map k t
r)
where
combine :: Map k a -> Maybe a -> Map k a -> Map k a
combine !Map k a
l' Maybe a
mx !Map k a
r' = case Maybe a
mx of
Maybe a
Nothing -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l' Map k a
r'
Just a
x' -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x' Map k a
l' Map k a
r'
mapEither :: (a -> Either b c) -> Map k a -> (Map k b, Map k c)
mapEither :: (a -> Either b c) -> Map k a -> (Map k b, Map k c)
mapEither a -> Either b c
f Map k a
m
= (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c)
forall k a b c.
(k -> a -> Either b c) -> Map k a -> (Map k b, Map k c)
mapEitherWithKey (\k
_ a
x -> a -> Either b c
f a
x) Map k a
m
mapEitherWithKey :: (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c)
mapEitherWithKey :: (k -> a -> Either b c) -> Map k a -> (Map k b, Map k c)
mapEitherWithKey k -> a -> Either b c
f0 Map k a
t0 = StrictPair (Map k b) (Map k c) -> (Map k b, Map k c)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Map k b) (Map k c) -> (Map k b, Map k c))
-> StrictPair (Map k b) (Map k c) -> (Map k b, Map k c)
forall a b. (a -> b) -> a -> b
$ (k -> a -> Either b c) -> Map k a -> StrictPair (Map k b) (Map k c)
forall {k} {t} {a} {a}.
(k -> t -> Either a a) -> Map k t -> StrictPair (Map k a) (Map k a)
go k -> a -> Either b c
f0 Map k a
t0
where
go :: (k -> t -> Either a a) -> Map k t -> StrictPair (Map k a) (Map k a)
go k -> t -> Either a a
_ Map k t
Tip = (Map k a
forall k a. Map k a
Tip Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
forall k a. Map k a
Tip)
go k -> t -> Either a a
f (Bin Int
_ k
kx t
x Map k t
l Map k t
r) = case k -> t -> Either a a
f k
kx t
x of
Left a
y -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
y Map k a
l1 Map k a
r1 Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l2 Map k a
r2
Right a
z -> Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l1 Map k a
r1 Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
z Map k a
l2 Map k a
r2
where
(Map k a
l1 :*: Map k a
l2) = (k -> t -> Either a a) -> Map k t -> StrictPair (Map k a) (Map k a)
go k -> t -> Either a a
f Map k t
l
(Map k a
r1 :*: Map k a
r2) = (k -> t -> Either a a) -> Map k t -> StrictPair (Map k a) (Map k a)
go k -> t -> Either a a
f Map k t
r
map :: (a -> b) -> Map k a -> Map k b
map :: (a -> b) -> Map k a -> Map k b
map a -> b
f = Map k a -> Map k b
go where
go :: Map k a -> Map k b
go Map k a
Tip = Map k b
forall k a. Map k a
Tip
go (Bin Int
sx k
kx a
x Map k a
l Map k a
r) = Int -> k -> b -> Map k b -> Map k b -> Map k b
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx (a -> b
f a
x) (Map k a -> Map k b
go Map k a
l) (Map k a -> Map k b
go Map k a
r)
#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 :: (k -> a -> b) -> Map k a -> Map k b
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b
mapWithKey k -> a -> b
_ Map k a
Tip = Map k b
forall k a. Map k a
Tip
mapWithKey k -> a -> b
f (Bin Int
sx k
kx a
x Map k a
l Map k a
r) = Int -> k -> b -> Map k b -> Map k b -> Map k b
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx (k -> a -> b
f k
kx a
x) ((k -> a -> b) -> Map k a -> Map k b
forall k a b. (k -> a -> b) -> Map k a -> Map k b
mapWithKey k -> a -> b
f Map k a
l) ((k -> a -> b) -> Map k a -> Map k b
forall k a b. (k -> a -> b) -> Map k a -> Map k b
mapWithKey k -> a -> b
f Map k a
r)
#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 => (k -> a -> t b) -> Map k a -> t (Map k b)
traverseWithKey :: (k -> a -> t b) -> Map k a -> t (Map k b)
traverseWithKey k -> a -> t b
f = Map k a -> t (Map k b)
go
where
go :: Map k a -> t (Map k b)
go Map k a
Tip = Map k b -> t (Map k b)
forall (f :: * -> *) a. Applicative f => a -> f a
Evidence bound by a type signature of the constraint type Applicative t
pure Map k b
forall k a. Map k a
Tip
go (Bin Int
1 k
k a
v Map k a
_ Map k a
_) = (\b
v' -> Int -> k -> b -> Map k b -> Map k b -> Map k b
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k b
v' Map k b
forall k a. Map k a
Tip Map k b
forall k a. Map k a
Tip) (b -> Map k b) -> t b -> t (Map k b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
External instance of the constraint type forall (f :: * -> *). Applicative f => Functor f
Evidence bound by a type signature of the constraint type Applicative t
<$> k -> a -> t b
f k
k a
v
go (Bin Int
s k
k a
v Map k a
l Map k a
r) = (Map k b -> b -> Map k b -> Map k b)
-> t (Map k b) -> t b -> t (Map k b) -> t (Map k b)
forall (f :: * -> *) a b c d.
Applicative f =>
(a -> b -> c -> d) -> f a -> f b -> f c -> f d
Evidence bound by a type signature of the constraint type Applicative t
liftA3 ((b -> Map k b -> Map k b -> Map k b)
-> Map k b -> b -> Map k b -> Map k b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Int -> k -> b -> Map k b -> Map k b -> Map k b
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
s k
k)) (Map k a -> t (Map k b)
go Map k a
l) (k -> a -> t b
f k
k a
v) (Map k a -> t (Map k b)
go Map k a
r)
{-# INLINE traverseWithKey #-}
mapAccum :: (a -> b -> (a,c)) -> a -> Map k b -> (a,Map k c)
mapAccum :: (a -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccum a -> b -> (a, c)
f a
a Map k b
m
= (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
forall a k b c.
(a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumWithKey (\a
a' k
_ b
x' -> a -> b -> (a, c)
f a
a' b
x') a
a Map k b
m
mapAccumWithKey :: (a -> k -> b -> (a,c)) -> a -> Map k b -> (a,Map k c)
mapAccumWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumWithKey a -> k -> b -> (a, c)
f a
a Map k b
t
= (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
forall a k b c.
(a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumL a -> k -> b -> (a, c)
f a
a Map k b
t
mapAccumL :: (a -> k -> b -> (a,c)) -> a -> Map k b -> (a,Map k c)
mapAccumL :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumL a -> k -> b -> (a, c)
_ a
a Map k b
Tip = (a
a,Map k c
forall k a. Map k a
Tip)
mapAccumL a -> k -> b -> (a, c)
f a
a (Bin Int
sx k
kx b
x Map k b
l Map k b
r) =
let (a
a1,Map k c
l') = (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
forall a k b c.
(a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumL a -> k -> b -> (a, c)
f a
a Map k b
l
(a
a2,c
x') = a -> k -> b -> (a, c)
f a
a1 k
kx b
x
(a
a3,Map k c
r') = (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
forall a k b c.
(a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumL a -> k -> b -> (a, c)
f a
a2 Map k b
r
in (a
a3,Int -> k -> c -> Map k c -> Map k c -> Map k c
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx c
x' Map k c
l' Map k c
r')
mapAccumRWithKey :: (a -> k -> b -> (a,c)) -> a -> Map k b -> (a,Map k c)
mapAccumRWithKey :: (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumRWithKey a -> k -> b -> (a, c)
_ a
a Map k b
Tip = (a
a,Map k c
forall k a. Map k a
Tip)
mapAccumRWithKey a -> k -> b -> (a, c)
f a
a (Bin Int
sx k
kx b
x Map k b
l Map k b
r) =
let (a
a1,Map k c
r') = (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
forall a k b c.
(a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumRWithKey a -> k -> b -> (a, c)
f a
a Map k b
r
(a
a2,c
x') = a -> k -> b -> (a, c)
f a
a1 k
kx b
x
(a
a3,Map k c
l') = (a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
forall a k b c.
(a -> k -> b -> (a, c)) -> a -> Map k b -> (a, Map k c)
mapAccumRWithKey a -> k -> b -> (a, c)
f a
a2 Map k b
l
in (a
a3,Int -> k -> c -> Map k c -> Map k c -> Map k c
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx c
x' Map k c
l' Map k c
r')
mapKeys :: Ord k2 => (k1->k2) -> Map k1 a -> Map k2 a
mapKeys :: (k1 -> k2) -> Map k1 a -> Map k2 a
mapKeys k1 -> k2
f = [(k2, a)] -> Map k2 a
forall k a. Ord k => [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k2
fromList ([(k2, a)] -> Map k2 a)
-> (Map k1 a -> [(k2, a)]) -> Map k1 a -> Map k2 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k1 -> a -> [(k2, a)] -> [(k2, a)])
-> [(k2, a)] -> Map k1 a -> [(k2, a)]
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey (\k1
k a
x [(k2, a)]
xs -> (k1 -> k2
f k1
k, a
x) (k2, a) -> [(k2, a)] -> [(k2, a)]
forall a. a -> [a] -> [a]
: [(k2, a)]
xs) []
#if __GLASGOW_HASKELL__
{-# INLINABLE mapKeys #-}
#endif
mapKeysWith :: Ord k2 => (a -> a -> a) -> (k1->k2) -> Map k1 a -> Map k2 a
mapKeysWith :: (a -> a -> a) -> (k1 -> k2) -> Map k1 a -> Map k2 a
mapKeysWith a -> a -> a
c k1 -> k2
f = (a -> a -> a) -> [(k2, a)] -> Map k2 a
forall k a. Ord k => (a -> a -> a) -> [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k2
fromListWith a -> a -> a
c ([(k2, a)] -> Map k2 a)
-> (Map k1 a -> [(k2, a)]) -> Map k1 a -> Map k2 a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (k1 -> a -> [(k2, a)] -> [(k2, a)])
-> [(k2, a)] -> Map k1 a -> [(k2, a)]
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey (\k1
k a
x [(k2, a)]
xs -> (k1 -> k2
f k1
k, a
x) (k2, a) -> [(k2, a)] -> [(k2, a)]
forall a. a -> [a] -> [a]
: [(k2, a)]
xs) []
#if __GLASGOW_HASKELL__
{-# INLINABLE mapKeysWith #-}
#endif
mapKeysMonotonic :: (k1->k2) -> Map k1 a -> Map k2 a
mapKeysMonotonic :: (k1 -> k2) -> Map k1 a -> Map k2 a
mapKeysMonotonic k1 -> k2
_ Map k1 a
Tip = Map k2 a
forall k a. Map k a
Tip
mapKeysMonotonic k1 -> k2
f (Bin Int
sz k1
k a
x Map k1 a
l Map k1 a
r) =
Int -> k2 -> a -> Map k2 a -> Map k2 a -> Map k2 a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sz (k1 -> k2
f k1
k) a
x ((k1 -> k2) -> Map k1 a -> Map k2 a
forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
mapKeysMonotonic k1 -> k2
f Map k1 a
l) ((k1 -> k2) -> Map k1 a -> Map k2 a
forall k1 k2 a. (k1 -> k2) -> Map k1 a -> Map k2 a
mapKeysMonotonic k1 -> k2
f Map k1 a
r)
foldr :: (a -> b -> b) -> b -> Map k a -> b
foldr :: (a -> b -> b) -> b -> Map k a -> b
foldr a -> b -> b
f b
z = b -> Map k a -> b
go b
z
where
go :: b -> Map k a -> b
go b
z' Map k a
Tip = b
z'
go b
z' (Bin Int
_ k
_ a
x Map k a
l Map k a
r) = b -> Map k a -> b
go (a -> b -> b
f a
x (b -> Map k a -> b
go b
z' Map k a
r)) Map k a
l
{-# INLINE foldr #-}
foldr' :: (a -> b -> b) -> b -> Map k a -> b
foldr' :: (a -> b -> b) -> b -> Map k a -> b
foldr' a -> b -> b
f b
z = b -> Map k a -> b
go b
z
where
go :: b -> Map k a -> b
go !b
z' Map k a
Tip = b
z'
go b
z' (Bin Int
_ k
_ a
x Map k a
l Map k a
r) = b -> Map k a -> b
go (a -> b -> b
f a
x (b -> Map k a -> b
go b
z' Map k a
r)) Map k a
l
{-# INLINE foldr' #-}
foldl :: (a -> b -> a) -> a -> Map k b -> a
foldl :: (a -> b -> a) -> a -> Map k b -> a
foldl a -> b -> a
f a
z = a -> Map k b -> a
go a
z
where
go :: a -> Map k b -> a
go a
z' Map k b
Tip = a
z'
go a
z' (Bin Int
_ k
_ b
x Map k b
l Map k b
r) = a -> Map k b -> a
go (a -> b -> a
f (a -> Map k b -> a
go a
z' Map k b
l) b
x) Map k b
r
{-# INLINE foldl #-}
foldl' :: (a -> b -> a) -> a -> Map k b -> a
foldl' :: (a -> b -> a) -> a -> Map k b -> a
foldl' a -> b -> a
f a
z = a -> Map k b -> a
go a
z
where
go :: a -> Map k b -> a
go !a
z' Map k b
Tip = a
z'
go a
z' (Bin Int
_ k
_ b
x Map k b
l Map k b
r) = a -> Map k b -> a
go (a -> b -> a
f (a -> Map k b -> a
go a
z' Map k b
l) b
x) Map k b
r
{-# INLINE foldl' #-}
foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey :: (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey k -> a -> b -> b
f b
z = b -> Map k a -> b
go b
z
where
go :: b -> Map k a -> b
go b
z' Map k a
Tip = b
z'
go b
z' (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = b -> Map k a -> b
go (k -> a -> b -> b
f k
kx a
x (b -> Map k a -> b
go b
z' Map k a
r)) Map k a
l
{-# INLINE foldrWithKey #-}
foldrWithKey' :: (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey' :: (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey' k -> a -> b -> b
f b
z = b -> Map k a -> b
go b
z
where
go :: b -> Map k a -> b
go !b
z' Map k a
Tip = b
z'
go b
z' (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = b -> Map k a -> b
go (k -> a -> b -> b
f k
kx a
x (b -> Map k a -> b
go b
z' Map k a
r)) Map k a
l
{-# INLINE foldrWithKey' #-}
foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a
foldlWithKey :: (a -> k -> b -> a) -> a -> Map k b -> a
foldlWithKey a -> k -> b -> a
f a
z = a -> Map k b -> a
go a
z
where
go :: a -> Map k b -> a
go a
z' Map k b
Tip = a
z'
go a
z' (Bin Int
_ k
kx b
x Map k b
l Map k b
r) = a -> Map k b -> a
go (a -> k -> b -> a
f (a -> Map k b -> a
go a
z' Map k b
l) k
kx b
x) Map k b
r
{-# INLINE foldlWithKey #-}
foldlWithKey' :: (a -> k -> b -> a) -> a -> Map k b -> a
foldlWithKey' :: (a -> k -> b -> a) -> a -> Map k b -> a
foldlWithKey' a -> k -> b -> a
f a
z = a -> Map k b -> a
go a
z
where
go :: a -> Map k b -> a
go !a
z' Map k b
Tip = a
z'
go a
z' (Bin Int
_ k
kx b
x Map k b
l Map k b
r) = a -> Map k b -> a
go (a -> k -> b -> a
f (a -> Map k b -> a
go a
z' Map k b
l) k
kx b
x) Map k b
r
{-# INLINE foldlWithKey' #-}
foldMapWithKey :: Monoid m => (k -> a -> m) -> Map k a -> m
foldMapWithKey :: (k -> a -> m) -> Map k a -> m
foldMapWithKey k -> a -> m
f = Map k a -> m
go
where
go :: Map k a -> m
go Map k a
Tip = m
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid m
mempty
go (Bin Int
1 k
k a
v Map k a
_ Map k a
_) = k -> a -> m
f k
k a
v
go (Bin Int
_ k
k a
v Map k a
l Map k a
r) = Map k a -> m
go Map k a
l m -> m -> m
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid m
`mappend` (k -> a -> m
f k
k a
v m -> m -> m
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid m
`mappend` Map k a -> m
go Map k a
r)
{-# INLINE foldMapWithKey #-}
elems :: Map k a -> [a]
elems :: Map k a -> [a]
elems = (a -> [a] -> [a]) -> [a] -> Map k a -> [a]
forall a b k. (a -> b -> b) -> b -> Map k a -> b
foldr (:) []
keys :: Map k a -> [k]
keys :: Map k a -> [k]
keys = (k -> a -> [k] -> [k]) -> [k] -> Map k a -> [k]
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey (\k
k a
_ [k]
ks -> k
k k -> [k] -> [k]
forall a. a -> [a] -> [a]
: [k]
ks) []
assocs :: Map k a -> [(k,a)]
assocs :: Map k a -> [(k, a)]
assocs Map k a
m
= Map k a -> [(k, a)]
forall k a. Map k a -> [(k, a)]
toAscList Map k a
m
keysSet :: Map k a -> Set.Set k
keysSet :: Map k a -> Set k
keysSet Map k a
Tip = Set k
forall a. Set a
Set.Tip
keysSet (Bin Int
sz k
kx a
_ Map k a
l Map k a
r) = Int -> k -> Set k -> Set k -> Set k
forall a. Int -> a -> Set a -> Set a -> Set a
Set.Bin Int
sz k
kx (Map k a -> Set k
forall k a. Map k a -> Set k
keysSet Map k a
l) (Map k a -> Set k
forall k a. Map k a -> Set k
keysSet Map k a
r)
fromSet :: (k -> a) -> Set.Set k -> Map k a
fromSet :: (k -> a) -> Set k -> Map k a
fromSet k -> a
_ Set k
Set.Tip = Map k a
forall k a. Map k a
Tip
fromSet k -> a
f (Set.Bin Int
sz k
x Set k
l Set k
r) = Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sz k
x (k -> a
f k
x) ((k -> a) -> Set k -> Map k a
forall k a. (k -> a) -> Set k -> Map k a
fromSet k -> a
f Set k
l) ((k -> a) -> Set k -> Map k a
forall k a. (k -> a) -> Set k -> Map k a
fromSet k -> a
f Set k
r)
#if __GLASGOW_HASKELL__ >= 708
instance (Ord k) => GHCExts.IsList (Map k v) where
type Item (Map k v) = (k,v)
fromList :: [Item (Map k v)] -> Map k v
fromList = [Item (Map k v)] -> Map k v
forall k a. Ord k => [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k
fromList
toList :: Map k v -> [Item (Map k v)]
toList = Map k v -> [Item (Map k v)]
forall k a. Map k a -> [(k, a)]
toList
#endif
fromList :: Ord k => [(k,a)] -> Map k a
fromList :: [(k, a)] -> Map k a
fromList [] = Map k a
forall k a. Map k a
Tip
fromList [(k
kx, a
x)] = Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip
fromList ((k
kx0, a
x0) : [(k, a)]
xs0) | k -> [(k, a)] -> Bool
forall {a} {b}. Ord a => a -> [(a, b)] -> Bool
Evidence bound by a type signature of the constraint type Ord k
not_ordered k
kx0 [(k, a)]
xs0 = Map k a -> [(k, a)] -> Map k a
forall {t :: * -> *} {k} {a}.
(Foldable t, Ord k) =>
Map k a -> t (k, a) -> Map k a
Evidence bound by a type signature of the constraint type Ord k
External instance of the constraint type Foldable []
fromList' (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx0 a
x0 Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) [(k, a)]
xs0
| Bool
otherwise = Int -> Map k a -> [(k, a)] -> Map k a
forall {k} {t} {a}.
(Ord k, Num t, Bits t) =>
t -> Map k a -> [(k, a)] -> Map k a
External instance of the constraint type Bits Int
External instance of the constraint type Num Int
Evidence bound by a type signature of the constraint type Ord k
go (Int
1::Int) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx0 a
x0 Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) [(k, a)]
xs0
where
not_ordered :: a -> [(a, b)] -> Bool
not_ordered a
_ [] = Bool
False
not_ordered a
kx ((a
ky,b
_) : [(a, b)]
_) = a
kx a -> a -> Bool
forall a. Ord a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Ord a
>= a
ky
{-# INLINE not_ordered #-}
fromList' :: Map k a -> t (k, a) -> Map k a
fromList' Map k a
t0 t (k, a)
xs = (Map k a -> (k, a) -> Map k a) -> Map k a -> t (k, a) -> Map k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
Evidence bound by a type signature of the constraint type Foldable t
Foldable.foldl' Map k a -> (k, a) -> Map k a
forall {k} {a}. Ord k => Map k a -> (k, a) -> Map k a
Evidence bound by a type signature of the constraint type Ord k
ins Map k a
t0 t (k, a)
xs
where ins :: Map k a -> (k, a) -> Map k a
ins Map k a
t (k
k,a
x) = k -> a -> Map k a -> Map k a
forall k a. Ord k => k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insert k
k a
x Map k a
t
go :: t -> Map k a -> [(k, a)] -> Map k a
go !t
_ Map k a
t [] = Map k a
t
go t
_ Map k a
t [(k
kx, a
x)] = k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMax k
kx a
x Map k a
t
go t
s Map k a
l xs :: [(k, a)]
xs@((k
kx, a
x) : [(k, a)]
xss) | k -> [(k, a)] -> Bool
forall {a} {b}. Ord a => a -> [(a, b)] -> Bool
Evidence bound by a type signature of the constraint type Ord k
not_ordered k
kx [(k, a)]
xss = Map k a -> [(k, a)] -> Map k a
forall {t :: * -> *} {k} {a}.
(Foldable t, Ord k) =>
Map k a -> t (k, a) -> Map k a
Evidence bound by a type signature of the constraint type Ord k
External instance of the constraint type Foldable []
fromList' Map k a
l [(k, a)]
xs
| Bool
otherwise = case t -> [(k, a)] -> (Map k a, [(k, a)], [(k, a)])
forall {a} {k} {a}.
(Num a, Ord k, Bits a) =>
a -> [(k, a)] -> (Map k a, [(k, a)], [(k, a)])
Evidence bound by a type signature of the constraint type Bits t
Evidence bound by a type signature of the constraint type Ord k
Evidence bound by a type signature of the constraint type Num t
create t
s [(k, a)]
xss of
(Map k a
r, [(k, a)]
ys, []) -> t -> Map k a -> [(k, a)] -> Map k a
go (t
s t -> Int -> t
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits t
`shiftL` Int
1) (k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
r) [(k, a)]
ys
(Map k a
r, [(k, a)]
_, [(k, a)]
ys) -> Map k a -> [(k, a)] -> Map k a
forall {t :: * -> *} {k} {a}.
(Foldable t, Ord k) =>
Map k a -> t (k, a) -> Map k a
Evidence bound by a type signature of the constraint type Ord k
External instance of the constraint type Foldable []
fromList' (k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
r) [(k, a)]
ys
create :: a -> [(k, a)] -> (Map k a, [(k, a)], [(k, a)])
create !a
_ [] = (Map k a
forall k a. Map k a
Tip, [], [])
create a
s xs :: [(k, a)]
xs@((k, a)
xp : [(k, a)]
xss)
| a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Bits a => Eq a
Evidence bound by a type signature of the constraint type Bits a
== a
1 = case (k, a)
xp of (k
kx, a
x) | k -> [(k, a)] -> Bool
forall {a} {b}. Ord a => a -> [(a, b)] -> Bool
Evidence bound by a type signature of the constraint type Ord k
not_ordered k
kx [(k, a)]
xss -> (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip, [], [(k, a)]
xss)
| Bool
otherwise -> (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip, [(k, a)]
xss, [])
| Bool
otherwise = case a -> [(k, a)] -> (Map k a, [(k, a)], [(k, a)])
create (a
s a -> Int -> a
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits a
`shiftR` Int
1) [(k, a)]
xs of
res :: (Map k a, [(k, a)], [(k, a)])
res@(Map k a
_, [], [(k, a)]
_) -> (Map k a, [(k, a)], [(k, a)])
res
(Map k a
l, [(k
ky, a
y)], [(k, a)]
zs) -> (k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMax k
ky a
y Map k a
l, [], [(k, a)]
zs)
(Map k a
l, ys :: [(k, a)]
ys@((k
ky, a
y):[(k, a)]
yss), [(k, a)]
_) | k -> [(k, a)] -> Bool
forall {a} {b}. Ord a => a -> [(a, b)] -> Bool
Evidence bound by a type signature of the constraint type Ord k
not_ordered k
ky [(k, a)]
yss -> (Map k a
l, [], [(k, a)]
ys)
| Bool
otherwise -> case a -> [(k, a)] -> (Map k a, [(k, a)], [(k, a)])
create (a
s a -> Int -> a
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits a
`shiftR` Int
1) [(k, a)]
yss of
(Map k a
r, [(k, a)]
zs, [(k, a)]
ws) -> (k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
ky a
y Map k a
l Map k a
r, [(k, a)]
zs, [(k, a)]
ws)
#if __GLASGOW_HASKELL__
{-# INLINABLE fromList #-}
#endif
fromListWith :: Ord k => (a -> a -> a) -> [(k,a)] -> Map k a
fromListWith :: (a -> a -> a) -> [(k, a)] -> Map k a
fromListWith a -> a -> a
f [(k, a)]
xs
= (k -> a -> a -> a) -> [(k, a)] -> Map k a
forall k a. Ord k => (k -> a -> a -> a) -> [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k
fromListWithKey (\k
_ a
x a
y -> a -> a -> a
f a
x a
y) [(k, a)]
xs
#if __GLASGOW_HASKELL__
{-# INLINABLE fromListWith #-}
#endif
fromListWithKey :: Ord k => (k -> a -> a -> a) -> [(k,a)] -> Map k a
fromListWithKey :: (k -> a -> a -> a) -> [(k, a)] -> Map k a
fromListWithKey k -> a -> a -> a
f [(k, a)]
xs
= (Map k a -> (k, a) -> Map k a) -> Map k a -> [(k, a)] -> Map k a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
External instance of the constraint type Foldable []
Foldable.foldl' Map k a -> (k, a) -> Map k a
ins Map k a
forall k a. Map k a
empty [(k, a)]
xs
where
ins :: Map k a -> (k, a) -> Map k a
ins Map k a
t (k
k,a
x) = (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
forall k a.
Ord k =>
(k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
Evidence bound by a type signature of the constraint type Ord k
insertWithKey k -> a -> a -> a
f k
k a
x Map k a
t
#if __GLASGOW_HASKELL__
{-# INLINABLE fromListWithKey #-}
#endif
toList :: Map k a -> [(k,a)]
toList :: Map k a -> [(k, a)]
toList = Map k a -> [(k, a)]
forall k a. Map k a -> [(k, a)]
toAscList
toAscList :: Map k a -> [(k,a)]
toAscList :: Map k a -> [(k, a)]
toAscList = (k -> a -> [(k, a)] -> [(k, a)]) -> [(k, a)] -> Map k a -> [(k, a)]
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey (\k
k a
x [(k, a)]
xs -> (k
k,a
x)(k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
:[(k, a)]
xs) []
toDescList :: Map k a -> [(k,a)]
toDescList :: Map k a -> [(k, a)]
toDescList = ([(k, a)] -> k -> a -> [(k, a)]) -> [(k, a)] -> Map k a -> [(k, a)]
forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
foldlWithKey (\[(k, a)]
xs k
k a
x -> (k
k,a
x)(k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
:[(k, a)]
xs) []
#if __GLASGOW_HASKELL__
foldrFB :: (k -> a -> b -> b) -> b -> Map k a -> b
foldrFB :: (k -> a -> b -> b) -> b -> Map k a -> b
foldrFB = (k -> a -> b -> b) -> b -> Map k a -> b
forall k a b. (k -> a -> b -> b) -> b -> Map k a -> b
foldrWithKey
{-# INLINE[0] foldrFB #-}
foldlFB :: (a -> k -> b -> a) -> a -> Map k b -> a
foldlFB :: (a -> k -> b -> a) -> a -> Map k b -> a
foldlFB = (a -> k -> b -> a) -> a -> Map k b -> a
forall a k b. (a -> k -> b -> a) -> a -> Map k b -> a
foldlWithKey
{-# INLINE[0] foldlFB #-}
{-# INLINE assocs #-}
{-# INLINE toList #-}
{-# NOINLINE[0] elems #-}
{-# NOINLINE[0] keys #-}
{-# NOINLINE[0] toAscList #-}
{-# NOINLINE[0] toDescList #-}
{-# RULES "Map.elems" [~1] forall m . elems m = build (\c n -> foldrFB (\_ x xs -> c x xs) n m) #-}
{-# RULES "Map.elemsBack" [1] foldrFB (\_ x xs -> x : xs) [] = elems #-}
{-# RULES "Map.keys" [~1] forall m . keys m = build (\c n -> foldrFB (\k _ xs -> c k xs) n m) #-}
{-# RULES "Map.keysBack" [1] foldrFB (\k _ xs -> k : xs) [] = keys #-}
{-# RULES "Map.toAscList" [~1] forall m . toAscList m = build (\c n -> foldrFB (\k x xs -> c (k,x) xs) n m) #-}
{-# RULES "Map.toAscListBack" [1] foldrFB (\k x xs -> (k, x) : xs) [] = toAscList #-}
{-# RULES "Map.toDescList" [~1] forall m . toDescList m = build (\c n -> foldlFB (\xs k x -> c (k,x) xs) n m) #-}
{-# RULES "Map.toDescListBack" [1] foldlFB (\xs k x -> (k, x) : xs) [] = toDescList #-}
#endif
fromAscList :: Eq k => [(k,a)] -> Map k a
fromAscList :: [(k, a)] -> Map k a
fromAscList [(k, a)]
xs
= [(k, a)] -> Map k a
forall k a. [(k, a)] -> Map k a
fromDistinctAscList ([(k, a)] -> [(k, a)]
forall {a} {b}. Eq a => [(a, b)] -> [(a, b)]
Evidence bound by a type signature of the constraint type Eq k
combineEq [(k, a)]
xs)
where
combineEq :: [(a, b)] -> [(a, b)]
combineEq [(a, b)]
xs'
= case [(a, b)]
xs' of
[] -> []
[(a, b)
x] -> [(a, b)
x]
((a, b)
x:[(a, b)]
xx) -> (a, b) -> [(a, b)] -> [(a, b)]
forall {a} {b}. Eq a => (a, b) -> [(a, b)] -> [(a, b)]
Evidence bound by a type signature of the constraint type Eq a
combineEq' (a, b)
x [(a, b)]
xx
combineEq' :: (a, b) -> [(a, b)] -> [(a, b)]
combineEq' (a, b)
z [] = [(a, b)
z]
combineEq' z :: (a, b)
z@(a
kz,b
_) (x :: (a, b)
x@(a
kx,b
xx):[(a, b)]
xs')
| a
kxa -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
==a
kz = (a, b) -> [(a, b)] -> [(a, b)]
combineEq' (a
kx,b
xx) [(a, b)]
xs'
| Bool
otherwise = (a, b)
z(a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
:(a, b) -> [(a, b)] -> [(a, b)]
combineEq' (a, b)
x [(a, b)]
xs'
#if __GLASGOW_HASKELL__
{-# INLINABLE fromAscList #-}
#endif
fromDescList :: Eq k => [(k,a)] -> Map k a
fromDescList :: [(k, a)] -> Map k a
fromDescList [(k, a)]
xs = [(k, a)] -> Map k a
forall k a. [(k, a)] -> Map k a
fromDistinctDescList ([(k, a)] -> [(k, a)]
forall {a} {b}. Eq a => [(a, b)] -> [(a, b)]
Evidence bound by a type signature of the constraint type Eq k
combineEq [(k, a)]
xs)
where
combineEq :: [(a, b)] -> [(a, b)]
combineEq [(a, b)]
xs'
= case [(a, b)]
xs' of
[] -> []
[(a, b)
x] -> [(a, b)
x]
((a, b)
x:[(a, b)]
xx) -> (a, b) -> [(a, b)] -> [(a, b)]
forall {a} {b}. Eq a => (a, b) -> [(a, b)] -> [(a, b)]
Evidence bound by a type signature of the constraint type Eq a
combineEq' (a, b)
x [(a, b)]
xx
combineEq' :: (a, b) -> [(a, b)] -> [(a, b)]
combineEq' (a, b)
z [] = [(a, b)
z]
combineEq' z :: (a, b)
z@(a
kz,b
_) (x :: (a, b)
x@(a
kx,b
xx):[(a, b)]
xs')
| a
kxa -> a -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq a
==a
kz = (a, b) -> [(a, b)] -> [(a, b)]
combineEq' (a
kx,b
xx) [(a, b)]
xs'
| Bool
otherwise = (a, b)
z(a, b) -> [(a, b)] -> [(a, b)]
forall a. a -> [a] -> [a]
:(a, b) -> [(a, b)] -> [(a, b)]
combineEq' (a, b)
x [(a, b)]
xs'
#if __GLASGOW_HASKELL__
{-# INLINABLE fromDescList #-}
#endif
fromAscListWith :: Eq k => (a -> a -> a) -> [(k,a)] -> Map k a
fromAscListWith :: (a -> a -> a) -> [(k, a)] -> Map k a
fromAscListWith a -> a -> a
f [(k, a)]
xs
= (k -> a -> a -> a) -> [(k, a)] -> Map k a
forall k a. Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Eq k
fromAscListWithKey (\k
_ a
x a
y -> a -> a -> a
f a
x a
y) [(k, a)]
xs
#if __GLASGOW_HASKELL__
{-# INLINABLE fromAscListWith #-}
#endif
fromDescListWith :: Eq k => (a -> a -> a) -> [(k,a)] -> Map k a
fromDescListWith :: (a -> a -> a) -> [(k, a)] -> Map k a
fromDescListWith a -> a -> a
f [(k, a)]
xs
= (k -> a -> a -> a) -> [(k, a)] -> Map k a
forall k a. Eq k => (k -> a -> a -> a) -> [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Eq k
fromDescListWithKey (\k
_ a
x a
y -> a -> a -> a
f a
x a
y) [(k, a)]
xs
#if __GLASGOW_HASKELL__
{-# INLINABLE fromDescListWith #-}
#endif
fromAscListWithKey :: Eq k => (k -> a -> a -> a) -> [(k,a)] -> Map k a
fromAscListWithKey :: (k -> a -> a -> a) -> [(k, a)] -> Map k a
fromAscListWithKey k -> a -> a -> a
f [(k, a)]
xs
= [(k, a)] -> Map k a
forall k a. [(k, a)] -> Map k a
fromDistinctAscList ((k -> a -> a -> a) -> [(k, a)] -> [(k, a)]
combineEq k -> a -> a -> a
f [(k, a)]
xs)
where
combineEq :: (k -> a -> a -> a) -> [(k, a)] -> [(k, a)]
combineEq k -> a -> a -> a
_ [(k, a)]
xs'
= case [(k, a)]
xs' of
[] -> []
[(k, a)
x] -> [(k, a)
x]
((k, a)
x:[(k, a)]
xx) -> (k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k, a)
x [(k, a)]
xx
combineEq' :: (k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k, a)
z [] = [(k, a)
z]
combineEq' z :: (k, a)
z@(k
kz,a
zz) (x :: (k, a)
x@(k
kx,a
xx):[(k, a)]
xs')
| k
kxk -> k -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq k
==k
kz = let yy :: a
yy = k -> a -> a -> a
f k
kx a
xx a
zz in (k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k
kx,a
yy) [(k, a)]
xs'
| Bool
otherwise = (k, a)
z(k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
:(k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k, a)
x [(k, a)]
xs'
#if __GLASGOW_HASKELL__
{-# INLINABLE fromAscListWithKey #-}
#endif
fromDescListWithKey :: Eq k => (k -> a -> a -> a) -> [(k,a)] -> Map k a
fromDescListWithKey :: (k -> a -> a -> a) -> [(k, a)] -> Map k a
fromDescListWithKey k -> a -> a -> a
f [(k, a)]
xs
= [(k, a)] -> Map k a
forall k a. [(k, a)] -> Map k a
fromDistinctDescList ((k -> a -> a -> a) -> [(k, a)] -> [(k, a)]
combineEq k -> a -> a -> a
f [(k, a)]
xs)
where
combineEq :: (k -> a -> a -> a) -> [(k, a)] -> [(k, a)]
combineEq k -> a -> a -> a
_ [(k, a)]
xs'
= case [(k, a)]
xs' of
[] -> []
[(k, a)
x] -> [(k, a)
x]
((k, a)
x:[(k, a)]
xx) -> (k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k, a)
x [(k, a)]
xx
combineEq' :: (k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k, a)
z [] = [(k, a)
z]
combineEq' z :: (k, a)
z@(k
kz,a
zz) (x :: (k, a)
x@(k
kx,a
xx):[(k, a)]
xs')
| k
kxk -> k -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq k
==k
kz = let yy :: a
yy = k -> a -> a -> a
f k
kx a
xx a
zz in (k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k
kx,a
yy) [(k, a)]
xs'
| Bool
otherwise = (k, a)
z(k, a) -> [(k, a)] -> [(k, a)]
forall a. a -> [a] -> [a]
:(k, a) -> [(k, a)] -> [(k, a)]
combineEq' (k, a)
x [(k, a)]
xs'
#if __GLASGOW_HASKELL__
{-# INLINABLE fromDescListWithKey #-}
#endif
fromDistinctAscList :: [(k,a)] -> Map k a
fromDistinctAscList :: [(k, a)] -> Map k a
fromDistinctAscList [] = Map k a
forall k a. Map k a
Tip
fromDistinctAscList ((k
kx0, a
x0) : [(k, a)]
xs0) = Int -> Map k a -> [(k, a)] -> Map k a
forall {t} {k} {a}.
(Num t, Bits t) =>
t -> Map k a -> [(k, a)] -> Map k a
External instance of the constraint type Bits Int
External instance of the constraint type Num Int
go (Int
1::Int) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx0 a
x0 Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) [(k, a)]
xs0
where
go :: t -> Map k a -> [(k, a)] -> Map k a
go !t
_ Map k a
t [] = Map k a
t
go t
s Map k a
l ((k
kx, a
x) : [(k, a)]
xs) = case t -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall {a} {k} {a}.
(Num a, Bits a) =>
a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
Evidence bound by a type signature of the constraint type Bits t
Evidence bound by a type signature of the constraint type Num t
create t
s [(k, a)]
xs of
(Map k a
r :*: [(k, a)]
ys) -> let !t' :: Map k a
t' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
r
in t -> Map k a -> [(k, a)] -> Map k a
go (t
s t -> Int -> t
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits t
`shiftL` Int
1) Map k a
t' [(k, a)]
ys
create :: a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
create !a
_ [] = (Map k a
forall k a. Map k a
Tip Map k a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall a b. a -> b -> StrictPair a b
:*: [])
create a
s xs :: [(k, a)]
xs@((k, a)
x' : [(k, a)]
xs')
| a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Bits a => Eq a
Evidence bound by a type signature of the constraint type Bits a
== a
1 = case (k, a)
x' of (k
kx, a
x) -> (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip Map k a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall a b. a -> b -> StrictPair a b
:*: [(k, a)]
xs')
| Bool
otherwise = case a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
create (a
s a -> Int -> a
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits a
`shiftR` Int
1) [(k, a)]
xs of
res :: StrictPair (Map k a) [(k, a)]
res@(Map k a
_ :*: []) -> StrictPair (Map k a) [(k, a)]
res
(Map k a
l :*: (k
ky, a
y):[(k, a)]
ys) -> case a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
create (a
s a -> Int -> a
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits a
`shiftR` Int
1) [(k, a)]
ys of
(Map k a
r :*: [(k, a)]
zs) -> (k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
ky a
y Map k a
l Map k a
r Map k a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall a b. a -> b -> StrictPair a b
:*: [(k, a)]
zs)
fromDistinctDescList :: [(k,a)] -> Map k a
fromDistinctDescList :: [(k, a)] -> Map k a
fromDistinctDescList [] = Map k a
forall k a. Map k a
Tip
fromDistinctDescList ((k
kx0, a
x0) : [(k, a)]
xs0) = Int -> Map k a -> [(k, a)] -> Map k a
forall {t} {k} {a}.
(Num t, Bits t) =>
t -> Map k a -> [(k, a)] -> Map k a
External instance of the constraint type Bits Int
External instance of the constraint type Num Int
go (Int
1 :: Int) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx0 a
x0 Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) [(k, a)]
xs0
where
go :: t -> Map k a -> [(k, a)] -> Map k a
go !t
_ Map k a
t [] = Map k a
t
go t
s Map k a
r ((k
kx, a
x) : [(k, a)]
xs) = case t -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall {a} {k} {a}.
(Num a, Bits a) =>
a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
Evidence bound by a type signature of the constraint type Bits t
Evidence bound by a type signature of the constraint type Num t
create t
s [(k, a)]
xs of
(Map k a
l :*: [(k, a)]
ys) -> let !t' :: Map k a
t' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
r
in t -> Map k a -> [(k, a)] -> Map k a
go (t
s t -> Int -> t
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits t
`shiftL` Int
1) Map k a
t' [(k, a)]
ys
create :: a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
create !a
_ [] = (Map k a
forall k a. Map k a
Tip Map k a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall a b. a -> b -> StrictPair a b
:*: [])
create a
s xs :: [(k, a)]
xs@((k, a)
x' : [(k, a)]
xs')
| a
s a -> a -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Bits a => Eq a
Evidence bound by a type signature of the constraint type Bits a
== a
1 = case (k, a)
x' of (k
kx, a
x) -> (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
kx a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip Map k a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall a b. a -> b -> StrictPair a b
:*: [(k, a)]
xs')
| Bool
otherwise = case a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
create (a
s a -> Int -> a
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits a
`shiftR` Int
1) [(k, a)]
xs of
res :: StrictPair (Map k a) [(k, a)]
res@(Map k a
_ :*: []) -> StrictPair (Map k a) [(k, a)]
res
(Map k a
r :*: (k
ky, a
y):[(k, a)]
ys) -> case a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
create (a
s a -> Int -> a
forall a. Bits a => a -> Int -> a
Evidence bound by a type signature of the constraint type Bits a
`shiftR` Int
1) [(k, a)]
ys of
(Map k a
l :*: [(k, a)]
zs) -> (k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
ky a
y Map k a
l Map k a
r Map k a -> [(k, a)] -> StrictPair (Map k a) [(k, a)]
forall a b. a -> b -> StrictPair a b
:*: [(k, a)]
zs)
split :: Ord k => k -> Map k a -> (Map k a,Map k a)
split :: k -> Map k a -> (Map k a, Map k a)
split !k
k0 Map k a
t0 = StrictPair (Map k a) (Map k a) -> (Map k a, Map k a)
forall a b. StrictPair a b -> (a, b)
toPair (StrictPair (Map k a) (Map k a) -> (Map k a, Map k a))
-> StrictPair (Map k a) (Map k a) -> (Map k a, Map k a)
forall a b. (a -> b) -> a -> b
$ k -> Map k a -> StrictPair (Map k a) (Map k a)
forall {k} {a}.
Ord k =>
k -> Map k a -> StrictPair (Map k a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k
k0 Map k a
t0
where
go :: k -> Map k a -> StrictPair (Map k a) (Map k a)
go k
k Map k a
t =
case Map k a
t of
Map k a
Tip -> Map k a
forall k a. Map k a
Tip Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
forall k a. Map k a
Tip
Bin Int
_ k
kx a
x Map k a
l Map k a
r -> case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> let (Map k a
lt :*: Map k a
gt) = k -> Map k a -> StrictPair (Map k a) (Map k a)
go k
k Map k a
l in Map k a
lt Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
gt Map k a
r
Ordering
GT -> let (Map k a
lt :*: Map k a
gt) = k -> Map k a -> StrictPair (Map k a) (Map k a)
go k
k Map k a
r in k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
lt Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
gt
Ordering
EQ -> (Map k a
l Map k a -> Map k a -> StrictPair (Map k a) (Map k a)
forall a b. a -> b -> StrictPair a b
:*: Map k a
r)
#if __GLASGOW_HASKELL__
{-# INLINABLE split #-}
#endif
splitLookup :: Ord k => k -> Map k a -> (Map k a,Maybe a,Map k a)
splitLookup :: k -> Map k a -> (Map k a, Maybe a, Map k a)
splitLookup k
k0 Map k a
m = case k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
forall k a.
Ord k =>
k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k
k0 Map k a
m of
StrictTriple Map k a
l Maybe a
mv Map k a
r -> (Map k a
l, Maybe a
mv, Map k a
r)
where
go :: Ord k => k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
go :: k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
go !k
k Map k a
t =
case Map k a
t of
Map k a
Tip -> Map k a
-> Maybe a -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
forall k a. Map k a
Tip Maybe a
forall a. Maybe a
Nothing Map k a
forall k a. Map k a
Tip
Bin Int
_ k
kx a
x Map k a
l Map k a
r -> case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> let StrictTriple Map k a
lt Maybe a
z Map k a
gt = k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
forall k a.
Ord k =>
k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k
k Map k a
l
!gt' :: Map k a
gt' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
gt Map k a
r
in Map k a
-> Maybe a -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
lt Maybe a
z Map k a
gt'
Ordering
GT -> let StrictTriple Map k a
lt Maybe a
z Map k a
gt = k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
forall k a.
Ord k =>
k -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k
k Map k a
r
!lt' :: Map k a
lt' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
lt
in Map k a
-> Maybe a -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
lt' Maybe a
z Map k a
gt
Ordering
EQ -> Map k a
-> Maybe a -> Map k a -> StrictTriple (Map k a) (Maybe a) (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
l (a -> Maybe a
forall a. a -> Maybe a
Just a
x) Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE splitLookup #-}
#endif
splitMember :: Ord k => k -> Map k a -> (Map k a,Bool,Map k a)
splitMember :: k -> Map k a -> (Map k a, Bool, Map k a)
splitMember k
k0 Map k a
m = case k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
forall k a.
Ord k =>
k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k
k0 Map k a
m of
StrictTriple Map k a
l Bool
mv Map k a
r -> (Map k a
l, Bool
mv, Map k a
r)
where
go :: Ord k => k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
go :: k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
go !k
k Map k a
t =
case Map k a
t of
Map k a
Tip -> Map k a -> Bool -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
forall k a. Map k a
Tip Bool
False Map k a
forall k a. Map k a
Tip
Bin Int
_ k
kx a
x Map k a
l Map k a
r -> case k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare k
k k
kx of
Ordering
LT -> let StrictTriple Map k a
lt Bool
z Map k a
gt = k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
forall k a.
Ord k =>
k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k
k Map k a
l
!gt' :: Map k a
gt' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
gt Map k a
r
in Map k a -> Bool -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
lt Bool
z Map k a
gt'
Ordering
GT -> let StrictTriple Map k a
lt Bool
z Map k a
gt = k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
forall k a.
Ord k =>
k -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
Evidence bound by a type signature of the constraint type Ord k
go k
k Map k a
r
!lt' :: Map k a
lt' = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
lt
in Map k a -> Bool -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
lt' Bool
z Map k a
gt
Ordering
EQ -> Map k a -> Bool -> Map k a -> StrictTriple (Map k a) Bool (Map k a)
forall a b c. a -> b -> c -> StrictTriple a b c
StrictTriple Map k a
l Bool
True Map k a
r
#if __GLASGOW_HASKELL__
{-# INLINABLE splitMember #-}
#endif
data StrictTriple a b c = StrictTriple !a !b !c
link :: k -> a -> Map k a -> Map k a -> Map k a
link :: k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
Tip Map k a
r = k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMin k
kx a
x Map k a
r
link k
kx a
x Map k a
l Map k a
Tip = k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMax k
kx a
x Map k a
l
link k
kx a
x l :: Map k a
l@(Bin Int
sizeL k
ky a
y Map k a
ly Map k a
ry) r :: Map k a
r@(Bin Int
sizeR k
kz a
z Map k a
lz Map k a
rz)
| Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
sizeL Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
sizeR = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
kz a
z (k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
l Map k a
lz) Map k a
rz
| Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
sizeR Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
sizeL = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
ly (k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
link k
kx a
x Map k a
ry Map k a
r)
| Bool
otherwise = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
bin k
kx a
x Map k a
l Map k a
r
insertMax,insertMin :: k -> a -> Map k a -> Map k a
insertMax :: k -> a -> Map k a -> Map k a
insertMax k
kx a
x Map k a
t
= case Map k a
t of
Map k a
Tip -> k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x
Bin Int
_ k
ky a
y Map k a
l Map k a
r
-> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
ky a
y Map k a
l (k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMax k
kx a
x Map k a
r)
insertMin :: k -> a -> Map k a -> Map k a
insertMin k
kx a
x Map k a
t
= case Map k a
t of
Map k a
Tip -> k -> a -> Map k a
forall k a. k -> a -> Map k a
singleton k
kx a
x
Bin Int
_ k
ky a
y Map k a
l Map k a
r
-> k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y (k -> a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a
insertMin k
kx a
x Map k a
l) Map k a
r
link2 :: Map k a -> Map k a -> Map k a
link2 :: Map k a -> Map k a -> Map k a
link2 Map k a
Tip Map k a
r = Map k a
r
link2 Map k a
l Map k a
Tip = Map k a
l
link2 l :: Map k a
l@(Bin Int
sizeL k
kx a
x Map k a
lx Map k a
rx) r :: Map k a
r@(Bin Int
sizeR k
ky a
y Map k a
ly Map k a
ry)
| Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
sizeL Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
sizeR = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
ky a
y (Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
l Map k a
ly) Map k a
ry
| Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
sizeR Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
sizeL = k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
kx a
x Map k a
lx (Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
link2 Map k a
rx Map k a
r)
| Bool
otherwise = Map k a -> Map k a -> Map k a
forall k a. Map k a -> Map k a -> Map k a
glue Map k a
l Map k a
r
glue :: Map k a -> Map k a -> Map k a
glue :: Map k a -> Map k a -> Map k a
glue Map k a
Tip Map k a
r = Map k a
r
glue Map k a
l Map k a
Tip = Map k a
l
glue l :: Map k a
l@(Bin Int
sl k
kl a
xl Map k a
ll Map k a
lr) r :: Map k a
r@(Bin Int
sr k
kr a
xr Map k a
rl Map k a
rr)
| Int
sl Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
sr = let !(MaxView k
km a
m Map k a
l') = k -> a -> Map k a -> Map k a -> MaxView k a
forall k a. k -> a -> Map k a -> Map k a -> MaxView k a
maxViewSure k
kl a
xl Map k a
ll Map k a
lr in k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR k
km a
m Map k a
l' Map k a
r
| Bool
otherwise = let !(MinView k
km a
m Map k a
r') = k -> a -> Map k a -> Map k a -> MinView k a
forall k a. k -> a -> Map k a -> Map k a -> MinView k a
minViewSure k
kr a
xr Map k a
rl Map k a
rr in k -> a -> Map k a -> Map k a -> Map k a
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL k
km a
m Map k a
l Map k a
r'
data MinView k a = MinView !k a !(Map k a)
data MaxView k a = MaxView !k a !(Map k a)
minViewSure :: k -> a -> Map k a -> Map k a -> MinView k a
minViewSure :: k -> a -> Map k a -> Map k a -> MinView k a
minViewSure = k -> a -> Map k a -> Map k a -> MinView k a
forall k a. k -> a -> Map k a -> Map k a -> MinView k a
go
where
go :: t -> t -> Map t t -> Map t t -> MinView t t
go t
k t
x Map t t
Tip Map t t
r = t -> t -> Map t t -> MinView t t
forall k a. k -> a -> Map k a -> MinView k a
MinView t
k t
x Map t t
r
go t
k t
x (Bin Int
_ t
kl t
xl Map t t
ll Map t t
lr) Map t t
r =
case t -> t -> Map t t -> Map t t -> MinView t t
go t
kl t
xl Map t t
ll Map t t
lr of
MinView t
km t
xm Map t t
l' -> t -> t -> Map t t -> MinView t t
forall k a. k -> a -> Map k a -> MinView k a
MinView t
km t
xm (t -> t -> Map t t -> Map t t -> Map t t
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceR t
k t
x Map t t
l' Map t t
r)
{-# NOINLINE minViewSure #-}
maxViewSure :: k -> a -> Map k a -> Map k a -> MaxView k a
maxViewSure :: k -> a -> Map k a -> Map k a -> MaxView k a
maxViewSure = k -> a -> Map k a -> Map k a -> MaxView k a
forall k a. k -> a -> Map k a -> Map k a -> MaxView k a
go
where
go :: t -> t -> Map t t -> Map t t -> MaxView t t
go t
k t
x Map t t
l Map t t
Tip = t -> t -> Map t t -> MaxView t t
forall k a. k -> a -> Map k a -> MaxView k a
MaxView t
k t
x Map t t
l
go t
k t
x Map t t
l (Bin Int
_ t
kr t
xr Map t t
rl Map t t
rr) =
case t -> t -> Map t t -> Map t t -> MaxView t t
go t
kr t
xr Map t t
rl Map t t
rr of
MaxView t
km t
xm Map t t
r' -> t -> t -> Map t t -> MaxView t t
forall k a. k -> a -> Map k a -> MaxView k a
MaxView t
km t
xm (t -> t -> Map t t -> Map t t -> Map t t
forall k a. k -> a -> Map k a -> Map k a -> Map k a
balanceL t
k t
x Map t t
l Map t t
r')
{-# NOINLINE maxViewSure #-}
deleteFindMin :: Map k a -> ((k,a),Map k a)
deleteFindMin :: Map k a -> ((k, a), Map k a)
deleteFindMin Map k a
t = case Map k a -> Maybe ((k, a), Map k a)
forall k a. Map k a -> Maybe ((k, a), Map k a)
minViewWithKey Map k a
t of
Maybe ((k, a), Map k a)
Nothing -> ([Char] -> (k, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.deleteFindMin: can not return the minimal element of an empty map", Map k a
forall k a. Map k a
Tip)
Just ((k, a), Map k a)
res -> ((k, a), Map k a)
res
deleteFindMax :: Map k a -> ((k,a),Map k a)
deleteFindMax :: Map k a -> ((k, a), Map k a)
deleteFindMax Map k a
t = case Map k a -> Maybe ((k, a), Map k a)
forall k a. Map k a -> Maybe ((k, a), Map k a)
maxViewWithKey Map k a
t of
Maybe ((k, a), Map k a)
Nothing -> ([Char] -> (k, a)
forall a. HasCallStack => [Char] -> a
error [Char]
"Map.deleteFindMax: can not return the maximal element of an empty map", Map k a
forall k a. Map k a
Tip)
Just ((k, a), Map k a)
res -> ((k, a), Map k a)
res
delta,ratio :: Int
delta :: Int
delta = Int
3
ratio :: Int
ratio = Int
2
balance :: k -> a -> Map k a -> Map k a -> Map k a
balance :: k -> a -> Map k a -> Map k a -> Map k a
balance k
k a
x Map k a
l Map k a
r = case Map k a
l of
Map k a
Tip -> case Map k a
r of
Map k a
Tip -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip
(Bin Int
_ k
_ a
_ Map k a
Tip Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
2 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
r
(Bin Int
_ k
rk a
rx Map k a
Tip rr :: Map k a
rr@(Bin Int
_ k
_ a
_ Map k a
_ Map k a
_)) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
rk a
rx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) Map k a
rr
(Bin Int
_ k
rk a
rx (Bin Int
_ k
rlk a
rlx Map k a
_ Map k a
_) Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
rlk a
rlx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
rk a
rx Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip)
(Bin Int
rs k
rk a
rx rl :: Map k a
rl@(Bin Int
rls k
rlk a
rlx Map k a
rll Map k a
rlr) rr :: Map k a
rr@(Bin Int
rrs k
_ a
_ Map k a
_ Map k a
_))
| Int
rls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
rrs -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rk a
rx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rls) k
k a
x Map k a
forall k a. Map k a
Tip Map k a
rl) Map k a
rr
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rlk a
rlx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rll) k
k a
x Map k a
forall k a. Map k a
Tip Map k a
rll) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rrsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rlr) k
rk a
rx Map k a
rlr Map k a
rr)
(Bin Int
ls k
lk a
lx Map k a
ll Map k a
lr) -> case Map k a
r of
Map k a
Tip -> case (Map k a
ll, Map k a
lr) of
(Map k a
Tip, Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
2 k
k a
x Map k a
l Map k a
forall k a. Map k a
Tip
(Map k a
Tip, (Bin Int
_ k
lrk a
lrx Map k a
_ Map k a
_)) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
lrk a
lrx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
lk a
lx Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip)
((Bin Int
_ k
_ a
_ Map k a
_ Map k a
_), Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
lk a
lx Map k a
ll (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip)
((Bin Int
lls k
_ a
_ Map k a
_ Map k a
_), (Bin Int
lrs k
lrk a
lrx Map k a
lrl Map k a
lrr))
| Int
lrs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
lls -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
ls) k
lk a
lx Map k a
ll (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lrs) k
k a
x Map k a
lr Map k a
forall k a. Map k a
Tip)
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
ls) k
lrk a
lrx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
llsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrl) k
lk a
lx Map k a
ll Map k a
lrl) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrr) k
k a
x Map k a
lrr Map k a
forall k a. Map k a
Tip)
(Bin Int
rs k
rk a
rx Map k a
rl Map k a
rr)
| Int
rs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
ls -> case (Map k a
rl, Map k a
rr) of
(Bin Int
rls k
rlk a
rlx Map k a
rll Map k a
rlr, Bin Int
rrs k
_ a
_ Map k a
_ Map k a
_)
| Int
rls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
rrs -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rk a
rx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rls) k
k a
x Map k a
l Map k a
rl) Map k a
rr
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rlk a
rlx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rll) k
k a
x Map k a
l Map k a
rll) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rrsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rlr) k
rk a
rx Map k a
rlr Map k a
rr)
(Map k a
_, Map k a
_) -> [Char] -> Map k a
forall a. HasCallStack => [Char] -> a
error [Char]
"Failure in Data.Map.balance"
| Int
ls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
rs -> case (Map k a
ll, Map k a
lr) of
(Bin Int
lls k
_ a
_ Map k a
_ Map k a
_, Bin Int
lrs k
lrk a
lrx Map k a
lrl Map k a
lrr)
| Int
lrs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
lls -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
lk a
lx Map k a
ll (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lrs) k
k a
x Map k a
lr Map k a
r)
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
lrk a
lrx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
llsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrl) k
lk a
lx Map k a
ll Map k a
lrl) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrr) k
k a
x Map k a
lrr Map k a
r)
(Map k a
_, Map k a
_) -> [Char] -> Map k a
forall a. HasCallStack => [Char] -> a
error [Char]
"Failure in Data.Map.balance"
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
k a
x Map k a
l Map k a
r
{-# NOINLINE balance #-}
balanceL :: k -> a -> Map k a -> Map k a -> Map k a
balanceL :: k -> a -> Map k a -> Map k a -> Map k a
balanceL k
k a
x Map k a
l Map k a
r = case Map k a
r of
Map k a
Tip -> case Map k a
l of
Map k a
Tip -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip
(Bin Int
_ k
_ a
_ Map k a
Tip Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
2 k
k a
x Map k a
l Map k a
forall k a. Map k a
Tip
(Bin Int
_ k
lk a
lx Map k a
Tip (Bin Int
_ k
lrk a
lrx Map k a
_ Map k a
_)) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
lrk a
lrx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
lk a
lx Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip)
(Bin Int
_ k
lk a
lx ll :: Map k a
ll@(Bin Int
_ k
_ a
_ Map k a
_ Map k a
_) Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
lk a
lx Map k a
ll (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip)
(Bin Int
ls k
lk a
lx ll :: Map k a
ll@(Bin Int
lls k
_ a
_ Map k a
_ Map k a
_) lr :: Map k a
lr@(Bin Int
lrs k
lrk a
lrx Map k a
lrl Map k a
lrr))
| Int
lrs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
lls -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
ls) k
lk a
lx Map k a
ll (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lrs) k
k a
x Map k a
lr Map k a
forall k a. Map k a
Tip)
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
ls) k
lrk a
lrx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
llsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrl) k
lk a
lx Map k a
ll Map k a
lrl) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrr) k
k a
x Map k a
lrr Map k a
forall k a. Map k a
Tip)
(Bin Int
rs k
_ a
_ Map k a
_ Map k a
_) -> case Map k a
l of
Map k a
Tip -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
k a
x Map k a
forall k a. Map k a
Tip Map k a
r
(Bin Int
ls k
lk a
lx Map k a
ll Map k a
lr)
| Int
ls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
rs -> case (Map k a
ll, Map k a
lr) of
(Bin Int
lls k
_ a
_ Map k a
_ Map k a
_, Bin Int
lrs k
lrk a
lrx Map k a
lrl Map k a
lrr)
| Int
lrs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
lls -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
lk a
lx Map k a
ll (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lrs) k
k a
x Map k a
lr Map k a
r)
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
lrk a
lrx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
llsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrl) k
lk a
lx Map k a
ll Map k a
lrl) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
lrr) k
k a
x Map k a
lrr Map k a
r)
(Map k a
_, Map k a
_) -> [Char] -> Map k a
forall a. HasCallStack => [Char] -> a
error [Char]
"Failure in Data.Map.balanceL"
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
k a
x Map k a
l Map k a
r
{-# NOINLINE balanceL #-}
balanceR :: k -> a -> Map k a -> Map k a -> Map k a
balanceR :: k -> a -> Map k a -> Map k a -> Map k a
balanceR k
k a
x Map k a
l Map k a
r = case Map k a
l of
Map k a
Tip -> case Map k a
r of
Map k a
Tip -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip
(Bin Int
_ k
_ a
_ Map k a
Tip Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
2 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
r
(Bin Int
_ k
rk a
rx Map k a
Tip rr :: Map k a
rr@(Bin Int
_ k
_ a
_ Map k a
_ Map k a
_)) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
rk a
rx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) Map k a
rr
(Bin Int
_ k
rk a
rx (Bin Int
_ k
rlk a
rlx Map k a
_ Map k a
_) Map k a
Tip) -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
3 k
rlk a
rlx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
k a
x Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
1 k
rk a
rx Map k a
forall k a. Map k a
Tip Map k a
forall k a. Map k a
Tip)
(Bin Int
rs k
rk a
rx rl :: Map k a
rl@(Bin Int
rls k
rlk a
rlx Map k a
rll Map k a
rlr) rr :: Map k a
rr@(Bin Int
rrs k
_ a
_ Map k a
_ Map k a
_))
| Int
rls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
rrs -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rk a
rx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rls) k
k a
x Map k a
forall k a. Map k a
Tip Map k a
rl) Map k a
rr
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rlk a
rlx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rll) k
k a
x Map k a
forall k a. Map k a
Tip Map k a
rll) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rrsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rlr) k
rk a
rx Map k a
rlr Map k a
rr)
(Bin Int
ls k
_ a
_ Map k a
_ Map k a
_) -> case Map k a
r of
Map k a
Tip -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
ls) k
k a
x Map k a
l Map k a
forall k a. Map k a
Tip
(Bin Int
rs k
rk a
rx Map k a
rl Map k a
rr)
| Int
rs Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
deltaInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
ls -> case (Map k a
rl, Map k a
rr) of
(Bin Int
rls k
rlk a
rlx Map k a
rll Map k a
rlr, Bin Int
rrs k
_ a
_ Map k a
_ Map k a
_)
| Int
rls Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
< Int
ratioInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
*Int
rrs -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rk a
rx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rls) k
k a
x Map k a
l Map k a
rl) Map k a
rr
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
rlk a
rlx (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rll) k
k a
x Map k a
l Map k a
rll) (Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rrsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Map k a -> Int
forall k a. Map k a -> Int
size Map k a
rlr) k
rk a
rx Map k a
rlr Map k a
rr)
(Map k a
_, Map k a
_) -> [Char] -> Map k a
forall a. HasCallStack => [Char] -> a
error [Char]
"Failure in Data.Map.balanceR"
| Bool
otherwise -> Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Int
1Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
lsInt -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+Int
rs) k
k a
x Map k a
l Map k a
r
{-# NOINLINE balanceR #-}
bin :: k -> a -> Map k a -> Map k a -> Map k a
bin :: k -> a -> Map k a -> Map k a -> Map k a
bin k
k a
x Map k a
l Map k a
r
= Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin (Map k a -> Int
forall k a. Map k a -> Int
size Map k a
l Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Map k a -> Int
forall k a. Map k a -> Int
size Map k a
r Int -> Int -> Int
forall a. Num a => a -> a -> a
External instance of the constraint type Num Int
+ Int
1) k
k a
x Map k a
l Map k a
r
{-# INLINE bin #-}
instance (Eq k,Eq a) => Eq (Map k a) where
Map k a
t1 == :: Map k a -> Map k a -> Bool
== Map k a
t2 = (Map k a -> Int
forall k a. Map k a -> Int
size Map k a
t1 Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Map k a -> Int
forall k a. Map k a -> Int
size Map k a
t2) Bool -> Bool -> Bool
&& (Map k a -> [(k, a)]
forall k a. Map k a -> [(k, a)]
toAscList Map k a
t1 [(k, a)] -> [(k, a)] -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type forall a. Eq a => Eq [a]
External instance of the constraint type forall a b. (Eq a, Eq b) => Eq (a, b)
Evidence bound by a type signature of the constraint type Eq k
Evidence bound by a type signature of the constraint type Eq a
== Map k a -> [(k, a)]
forall k a. Map k a -> [(k, a)]
toAscList Map k a
t2)
instance (Ord k, Ord v) => Ord (Map k v) where
compare :: Map k v -> Map k v -> Ordering
compare Map k v
m1 Map k v
m2 = [(k, v)] -> [(k, v)] -> Ordering
forall a. Ord a => a -> a -> Ordering
External instance of the constraint type forall a. Ord a => Ord [a]
External instance of the constraint type forall a b. (Ord a, Ord b) => Ord (a, b)
Evidence bound by a type signature of the constraint type Ord k
Evidence bound by a type signature of the constraint type Ord v
compare (Map k v -> [(k, v)]
forall k a. Map k a -> [(k, a)]
toAscList Map k v
m1) (Map k v -> [(k, v)]
forall k a. Map k a -> [(k, a)]
toAscList Map k v
m2)
#if MIN_VERSION_base(4,9,0)
instance Eq2 Map where
liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> Map a c -> Map b d -> Bool
liftEq2 a -> b -> Bool
eqk c -> d -> Bool
eqv Map a c
m Map b d
n =
Map a c -> Int
forall k a. Map k a -> Int
size Map a c
m Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
External instance of the constraint type Eq Int
== Map b d -> Int
forall k a. Map k a -> Int
size Map b d
n Bool -> Bool -> Bool
&& ((a, c) -> (b, d) -> Bool) -> [(a, c)] -> [(b, d)] -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
External instance of the constraint type Eq1 []
liftEq ((a -> b -> Bool) -> (c -> d -> Bool) -> (a, c) -> (b, d) -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
External instance of the constraint type Eq2 (,)
liftEq2 a -> b -> Bool
eqk c -> d -> Bool
eqv) (Map a c -> [(a, c)]
forall k a. Map k a -> [(k, a)]
toList Map a c
m) (Map b d -> [(b, d)]
forall k a. Map k a -> [(k, a)]
toList Map b d
n)
instance Eq k => Eq1 (Map k) where
liftEq :: (a -> b -> Bool) -> Map k a -> Map k b -> Bool
liftEq = (k -> k -> Bool) -> (a -> b -> Bool) -> Map k a -> Map k b -> Bool
forall (f :: * -> * -> *) a b c d.
Eq2 f =>
(a -> b -> Bool) -> (c -> d -> Bool) -> f a c -> f b d -> Bool
Instance of class: Eq2 of the constraint type Eq2 Map
liftEq2 k -> k -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq k
(==)
instance Ord2 Map where
liftCompare2 :: (a -> b -> Ordering)
-> (c -> d -> Ordering) -> Map a c -> Map b d -> Ordering
liftCompare2 a -> b -> Ordering
cmpk c -> d -> Ordering
cmpv Map a c
m Map b d
n =
((a, c) -> (b, d) -> Ordering) -> [(a, c)] -> [(b, d)] -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
External instance of the constraint type Ord1 []
liftCompare ((a -> b -> Ordering)
-> (c -> d -> Ordering) -> (a, c) -> (b, d) -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
External instance of the constraint type Ord2 (,)
liftCompare2 a -> b -> Ordering
cmpk c -> d -> Ordering
cmpv) (Map a c -> [(a, c)]
forall k a. Map k a -> [(k, a)]
toList Map a c
m) (Map b d -> [(b, d)]
forall k a. Map k a -> [(k, a)]
toList Map b d
n)
instance Ord k => Ord1 (Map k) where
liftCompare :: (a -> b -> Ordering) -> Map k a -> Map k b -> Ordering
liftCompare = (k -> k -> Ordering)
-> (a -> b -> Ordering) -> Map k a -> Map k b -> Ordering
forall (f :: * -> * -> *) a b c d.
Ord2 f =>
(a -> b -> Ordering)
-> (c -> d -> Ordering) -> f a c -> f b d -> Ordering
Instance of class: Ord2 of the constraint type Ord2 Map
liftCompare2 k -> k -> Ordering
forall a. Ord a => a -> a -> Ordering
Evidence bound by a type signature of the constraint type Ord k
compare
instance Show2 Map where
liftShowsPrec2 :: (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> Map a b
-> ShowS
liftShowsPrec2 Int -> a -> ShowS
spk [a] -> ShowS
slk Int -> b -> ShowS
spv [b] -> ShowS
slv Int
d Map a b
m =
(Int -> [(a, b)] -> ShowS) -> [Char] -> Int -> [(a, b)] -> ShowS
forall a. (Int -> a -> ShowS) -> [Char] -> Int -> a -> ShowS
showsUnaryWith ((Int -> (a, b) -> ShowS)
-> ([(a, b)] -> ShowS) -> Int -> [(a, b)] -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> f a -> ShowS
External instance of the constraint type Show1 []
liftShowsPrec Int -> (a, b) -> ShowS
sp [(a, b)] -> ShowS
sl) [Char]
"fromList" Int
d (Map a b -> [(a, b)]
forall k a. Map k a -> [(k, a)]
toList Map a b
m)
where
sp :: Int -> (a, b) -> ShowS
sp = (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> (a, b)
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
External instance of the constraint type Show2 (,)
liftShowsPrec2 Int -> a -> ShowS
spk [a] -> ShowS
slk Int -> b -> ShowS
spv [b] -> ShowS
slv
sl :: [(a, b)] -> ShowS
sl = (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> [(a, b)]
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> [f a b]
-> ShowS
External instance of the constraint type Show2 (,)
liftShowList2 Int -> a -> ShowS
spk [a] -> ShowS
slk Int -> b -> ShowS
spv [b] -> ShowS
slv
instance Show k => Show1 (Map k) where
liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> Map k a -> ShowS
liftShowsPrec = (Int -> k -> ShowS)
-> ([k] -> ShowS)
-> (Int -> a -> ShowS)
-> ([a] -> ShowS)
-> Int
-> Map k a
-> ShowS
forall (f :: * -> * -> *) a b.
Show2 f =>
(Int -> a -> ShowS)
-> ([a] -> ShowS)
-> (Int -> b -> ShowS)
-> ([b] -> ShowS)
-> Int
-> f a b
-> ShowS
Instance of class: Show2 of the constraint type Show2 Map
liftShowsPrec2 Int -> k -> ShowS
forall a. Show a => Int -> a -> ShowS
Evidence bound by a type signature of the constraint type Show k
showsPrec [k] -> ShowS
forall a. Show a => [a] -> ShowS
Evidence bound by a type signature of the constraint type Show k
showList
instance (Ord k, Read k) => Read1 (Map k) where
liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (Map k a)
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl = ([Char] -> ReadS (Map k a)) -> Int -> ReadS (Map k a)
forall a. ([Char] -> ReadS a) -> Int -> ReadS a
readsData (([Char] -> ReadS (Map k a)) -> Int -> ReadS (Map k a))
-> ([Char] -> ReadS (Map k a)) -> Int -> ReadS (Map k a)
forall a b. (a -> b) -> a -> b
$
(Int -> ReadS [(k, a)])
-> [Char] -> ([(k, a)] -> Map k a) -> [Char] -> ReadS (Map k a)
forall a t.
(Int -> ReadS a) -> [Char] -> (a -> t) -> [Char] -> ReadS t
readsUnaryWith ((Int -> ReadS (k, a)) -> ReadS [(k, a)] -> Int -> ReadS [(k, a)]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
External instance of the constraint type Read1 []
liftReadsPrec Int -> ReadS (k, a)
rp' ReadS [(k, a)]
rl') [Char]
"fromList" [(k, a)] -> Map k a
forall k a. Ord k => [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k
fromList
where
rp' :: Int -> ReadS (k, a)
rp' = (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (k, a)
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (f a)
External instance of the constraint type forall a. Read a => Read1 ((,) a)
Evidence bound by a type signature of the constraint type Read k
liftReadsPrec Int -> ReadS a
rp ReadS [a]
rl
rl' :: ReadS [(k, a)]
rl' = (Int -> ReadS a) -> ReadS [a] -> ReadS [(k, a)]
forall (f :: * -> *) a.
Read1 f =>
(Int -> ReadS a) -> ReadS [a] -> ReadS [f a]
External instance of the constraint type forall a. Read a => Read1 ((,) a)
Evidence bound by a type signature of the constraint type Read k
liftReadList Int -> ReadS a
rp ReadS [a]
rl
#endif
instance Functor (Map k) where
fmap :: (a -> b) -> Map k a -> Map k b
fmap a -> b
f Map k a
m = (a -> b) -> Map k a -> Map k b
forall a b k. (a -> b) -> Map k a -> Map k b
map a -> b
f Map k a
m
#ifdef __GLASGOW_HASKELL__
a
_ <$ :: a -> Map k b -> Map k a
<$ Map k b
Tip = Map k a
forall k a. Map k a
Tip
a
a <$ (Bin Int
sx k
kx b
_ Map k b
l Map k b
r) = Int -> k -> a -> Map k a -> Map k a -> Map k a
forall k a. Int -> k -> a -> Map k a -> Map k a -> Map k a
Bin Int
sx k
kx a
a (a
a a -> Map k b -> Map k a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
Instance of class: Functor of the constraint type forall k. Functor (Map k)
<$ Map k b
l) (a
a a -> Map k b -> Map k a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
Instance of class: Functor of the constraint type forall k. Functor (Map k)
<$ Map k b
r)
#endif
instance Traversable (Map k) where
traverse :: (a -> f b) -> Map k a -> f (Map k b)
traverse a -> f b
f = (k -> a -> f b) -> Map k a -> f (Map k b)
forall (t :: * -> *) k a b.
Applicative t =>
(k -> a -> t b) -> Map k a -> t (Map k b)
Evidence bound by a type signature of the constraint type Applicative f
traverseWithKey (\k
_ -> a -> f b
f)
{-# INLINE traverse #-}
instance Foldable.Foldable (Map k) where
fold :: Map k m -> m
fold = Map k m -> m
forall {a} {k}. Monoid a => Map k a -> a
Evidence bound by a type signature of the constraint type Monoid m
go
where go :: Map k a -> a
go Map k a
Tip = a
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid a
mempty
go (Bin Int
1 k
_ a
v Map k a
_ Map k a
_) = a
v
go (Bin Int
_ k
_ a
v Map k a
l Map k a
r) = Map k a -> a
go Map k a
l a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` (a
v a -> a -> a
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid a
`mappend` Map k a -> a
go Map k a
r)
{-# INLINABLE fold #-}
foldr :: (a -> b -> b) -> b -> Map k a -> b
foldr = (a -> b -> b) -> b -> Map k a -> b
forall a b k. (a -> b -> b) -> b -> Map k a -> b
foldr
{-# INLINE foldr #-}
foldl :: (b -> a -> b) -> b -> Map k a -> b
foldl = (b -> a -> b) -> b -> Map k a -> b
forall a b k. (a -> b -> a) -> a -> Map k b -> a
foldl
{-# INLINE foldl #-}
foldMap :: (a -> m) -> Map k a -> m
foldMap a -> m
f Map k a
t = Map k a -> m
go Map k a
t
where go :: Map k a -> m
go Map k a
Tip = m
forall a. Monoid a => a
Evidence bound by a type signature of the constraint type Monoid m
mempty
go (Bin Int
1 k
_ a
v Map k a
_ Map k a
_) = a -> m
f a
v
go (Bin Int
_ k
_ a
v Map k a
l Map k a
r) = Map k a -> m
go Map k a
l m -> m -> m
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid m
`mappend` (a -> m
f a
v m -> m -> m
forall a. Monoid a => a -> a -> a
Evidence bound by a type signature of the constraint type Monoid m
`mappend` Map k a -> m
go Map k a
r)
{-# INLINE foldMap #-}
foldl' :: (b -> a -> b) -> b -> Map k a -> b
foldl' = (b -> a -> b) -> b -> Map k a -> b
forall a b k. (a -> b -> a) -> a -> Map k b -> a
foldl'
{-# INLINE foldl' #-}
foldr' :: (a -> b -> b) -> b -> Map k a -> b
foldr' = (a -> b -> b) -> b -> Map k a -> b
forall a b k. (a -> b -> b) -> b -> Map k a -> b
foldr'
{-# INLINE foldr' #-}
#if MIN_VERSION_base(4,8,0)
length :: Map k a -> Int
length = Map k a -> Int
forall k a. Map k a -> Int
size
{-# INLINE length #-}
null :: Map k a -> Bool
null = Map k a -> Bool
forall k a. Map k a -> Bool
null
{-# INLINE null #-}
toList :: Map k a -> [a]
toList = Map k a -> [a]
forall k a. Map k a -> [a]
elems
{-# INLINE toList #-}
elem :: a -> Map k a -> Bool
elem = a -> Map k a -> Bool
forall {t} {k}. Eq t => t -> Map k t -> Bool
Evidence bound by a type signature of the constraint type Eq a
go
where go :: t -> Map k t -> Bool
go !t
_ Map k t
Tip = Bool
False
go t
x (Bin Int
_ k
_ t
v Map k t
l Map k t
r) = t
x t -> t -> Bool
forall a. Eq a => a -> a -> Bool
Evidence bound by a type signature of the constraint type Eq t
== t
v Bool -> Bool -> Bool
|| t -> Map k t -> Bool
go t
x Map k t
l Bool -> Bool -> Bool
|| t -> Map k t -> Bool
go t
x Map k t
r
{-# INLINABLE elem #-}
maximum :: Map k a -> a
maximum = Map k a -> a
forall {p} {k}. Ord p => Map k p -> p
Evidence bound by a type signature of the constraint type Ord a
start
where start :: Map k p -> p
start Map k p
Tip = [Char] -> p
forall a. HasCallStack => [Char] -> a
error [Char]
"Data.Foldable.maximum (for Data.Map): empty map"
start (Bin Int
_ k
_ p
v Map k p
l Map k p
r) = p -> Map k p -> p
forall {t} {k}. Ord t => t -> Map k t -> t
Evidence bound by a type signature of the constraint type Ord p
go (p -> Map k p -> p
forall {t} {k}. Ord t => t -> Map k t -> t
Evidence bound by a type signature of the constraint type Ord p
go p
v Map k p
l) Map k p
r
go :: t -> Map k t -> t
go !t
m Map k t
Tip = t
m
go t
m (Bin Int
_ k
_ t
v Map k t
l Map k t
r) = t -> Map k t -> t
go (t -> Map k t -> t
go (t -> t -> t
forall a. Ord a => a -> a -> a
Evidence bound by a type signature of the constraint type Ord t
max t
m t
v) Map k t
l) Map k t
r
{-# INLINABLE maximum #-}
minimum :: Map k a -> a
minimum = Map k a -> a
forall {p} {k}. Ord p => Map k p -> p
Evidence bound by a type signature of the constraint type Ord a
start
where start :: Map k p -> p
start Map k p
Tip = [Char] -> p
forall a. HasCallStack => [Char] -> a
error [Char]
"Data.Foldable.minimum (for Data.Map): empty map"
start (Bin Int
_ k
_ p
v Map k p
l Map k p
r) = p -> Map k p -> p
forall {t} {k}. Ord t => t -> Map k t -> t
Evidence bound by a type signature of the constraint type Ord p
go (p -> Map k p -> p
forall {t} {k}. Ord t => t -> Map k t -> t
Evidence bound by a type signature of the constraint type Ord p
go p
v Map k p
l) Map k p
r
go :: t -> Map k t -> t
go !t
m Map k t
Tip = t
m
go t
m (Bin Int
_ k
_ t
v Map k t
l Map k t
r) = t -> Map k t -> t
go (t -> Map k t -> t
go (t -> t -> t
forall a. Ord a => a -> a -> a
Evidence bound by a type signature of the constraint type Ord t
min t
m t
v) Map k t
l) Map k t
r
{-# INLINABLE minimum #-}
sum :: Map k a -> a
sum = (a -> a -> a) -> a -> Map k a -> a
forall a b k. (a -> b -> a) -> a -> Map k b -> a
foldl' a -> a -> a
forall a. Num a => a -> a -> a
Evidence bound by a type signature of the constraint type Num a
(+) a
0
{-# INLINABLE sum #-}
product :: Map k a -> a
product = (a -> a -> a) -> a -> Map k a -> a
forall a b k. (a -> b -> a) -> a -> Map k b -> a
foldl' a -> a -> a
forall a. Num a => a -> a -> a
Evidence bound by a type signature of the constraint type Num a
(*) a
1
{-# INLINABLE product #-}
#endif
instance (NFData k, NFData a) => NFData (Map k a) where
rnf :: Map k a -> ()
rnf Map k a
Tip = ()
rnf (Bin Int
_ k
kx a
x Map k a
l Map k a
r) = k -> ()
forall a. NFData a => a -> ()
Evidence bound by a type signature of the constraint type NFData k
rnf k
kx () -> () -> ()
`seq` a -> ()
forall a. NFData a => a -> ()
Evidence bound by a type signature of the constraint type NFData a
rnf a
x () -> () -> ()
`seq` Map k a -> ()
forall a. NFData a => a -> ()
Instance of class: NFData of the constraint type forall k a. (NFData k, NFData a) => NFData (Map k a)
Evidence bound by a type signature of the constraint type NFData k
Evidence bound by a type signature of the constraint type NFData a
rnf Map k a
l () -> () -> ()
`seq` Map k a -> ()
forall a. NFData a => a -> ()
Instance of class: NFData of the constraint type forall k a. (NFData k, NFData a) => NFData (Map k a)
Evidence bound by a type signature of the constraint type NFData k
Evidence bound by a type signature of the constraint type NFData a
rnf Map k a
r
instance (Ord k, Read k, Read e) => Read (Map k e) where
#ifdef __GLASGOW_HASKELL__
readPrec :: ReadPrec (Map k e)
readPrec = ReadPrec (Map k e) -> ReadPrec (Map k e)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (Map k e) -> ReadPrec (Map k e))
-> ReadPrec (Map k e) -> ReadPrec (Map k e)
forall a b. (a -> b) -> a -> b
$ Int -> ReadPrec (Map k e) -> ReadPrec (Map k e)
forall a. Int -> ReadPrec a -> ReadPrec a
prec Int
10 (ReadPrec (Map k e) -> ReadPrec (Map k e))
-> ReadPrec (Map k e) -> ReadPrec (Map k e)
forall a b. (a -> b) -> a -> b
$ do
Ident [Char]
"fromList" <- ReadPrec Lexeme
lexP
[(k, e)]
xs <- ReadPrec [(k, e)]
forall a. Read a => ReadPrec a
External instance of the constraint type forall a. Read a => Read [a]
External instance of the constraint type forall a b. (Read a, Read b) => Read (a, b)
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read e
readPrec
Map k e -> ReadPrec (Map k e)
forall (m :: * -> *) a. Monad m => a -> m a
External instance of the constraint type Monad ReadPrec
return ([(k, e)] -> Map k e
forall k a. Ord k => [(k, a)] -> Map k a
Evidence bound by a type signature of the constraint type Ord k
fromList [(k, e)]
xs)
readListPrec :: ReadPrec [Map k e]
readListPrec = ReadPrec [Map k e]
forall a. Read a => ReadPrec [a]
Instance of class: Read of the constraint type forall k e. (Ord k, Read k, Read e) => Read (Map k e)
Evidence bound by a type signature of the constraint type Ord k
Evidence bound by a type signature of the constraint type Read k
Evidence bound by a type signature of the constraint type Read e
readListPrecDefault
#else
readsPrec p = readParen (p > 10) $ \ r -> do
("fromList",s) <- lex r
(xs,t) <- reads s
return (fromList xs,t)
#endif
instance (Show k, Show a) => Show (Map k a) where
showsPrec :: Int -> Map k a -> ShowS
showsPrec Int
d Map k a
m = Bool -> ShowS -> ShowS
showParen (Int
d Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
External instance of the constraint type Ord Int
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
[Char] -> ShowS
showString [Char]
"fromList " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(k, a)] -> ShowS
forall a. Show a => a -> ShowS
External instance of the constraint type forall a. Show a => Show [a]
External instance of the constraint type forall a b. (Show a, Show b) => Show (a, b)
Evidence bound by a type signature of the constraint type Show k
Evidence bound by a type signature of the constraint type Show a
shows (Map k a -> [(k, a)]
forall k a. Map k a -> [(k, a)]
toList Map k a
m)
INSTANCE_TYPEABLE2(Map)
splitRoot :: Map k b -> [Map k b]
splitRoot :: Map k b -> [Map k b]
splitRoot Map k b
orig =
case Map k b
orig of
Map k b
Tip -> []
Bin Int
_ k
k b
v Map k b
l Map k b
r -> [Map k b
l, k -> b -> Map k b
forall k a. k -> a -> Map k a
singleton k
k b
v, Map k b
r]
{-# INLINE splitRoot #-}