{-# LANGUAGE BangPatterns       #-}
{-# LANGUAGE CPP                #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ViewPatterns       #-}
{-# OPTIONS_HADDOCK not-home    #-}
module Data.IntMap.NonEmpty.Internal (
  
    NEIntMap(..)
  , Key
  , singleton
  , nonEmptyMap
  , withNonEmpty
  , fromList
  , toList
  , map
  , insertWith
  , union
  , unions
  , elems
  , size
  , toMap
  
  , foldr
  , foldr'
  , foldr1
  , foldl
  , foldl'
  , foldl1
  
  , traverseWithKey
  , traverseWithKey1
  , foldMapWithKey
  , traverseMapWithKey
  
  , insertMinMap
  , insertMaxMap
  
  , valid
  
  , lookupMinMap
  , lookupMaxMap
  ) where
import           Control.Applicative
import           Control.Comonad
import           Control.DeepSeq
import           Control.Monad
import           Data.Coerce
import           Data.Data
import           Data.Function
import           Data.Functor.Alt
import           Data.Functor.Classes
import           Data.Functor.Invariant
import           Data.IntMap.Internal       (IntMap(..), Key)
import           Data.List.NonEmpty         (NonEmpty(..))
import           Data.Maybe
import           Data.Semigroup
import           Data.Semigroup.Foldable    (Foldable1(fold1))
import           Data.Semigroup.Traversable (Traversable1(..))
import           Prelude hiding             (foldr1, foldl1, foldr, foldl, map)
import           Text.Read
import qualified Data.Aeson                 as A
import qualified Data.Foldable              as F
import qualified Data.IntMap                as M
import qualified Data.List                  as L
import qualified Data.Semigroup.Foldable    as F1
data NEIntMap a =
    NEIntMap { NEIntMap a -> Key
neimK0     :: !Key    
             , NEIntMap a -> a
neimV0     :: a
             , NEIntMap a -> IntMap a
neimIntMap :: !(IntMap a)
             }
  deriving (Typeable)
instance Eq a => Eq (NEIntMap a) where
    NEIntMap a
t1 == :: NEIntMap a -> NEIntMap a -> Bool
== NEIntMap a
t2 = IntMap a -> Key
forall a. IntMap a -> Key
M.size (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
neimIntMap NEIntMap a
t1) Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== IntMap a -> Key
forall a. IntMap a -> Key
M.size (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
neimIntMap NEIntMap a
t2)
            Bool -> Bool -> Bool
&& NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap a
t1 NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool
forall a. Eq a => a -> a -> Bool
== NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap a
t2
instance Ord a => Ord (NEIntMap a) where
    compare :: NEIntMap a -> NEIntMap a -> Ordering
compare = NonEmpty (Key, a) -> NonEmpty (Key, a) -> Ordering
forall a. Ord a => a -> a -> Ordering
compare (NonEmpty (Key, a) -> NonEmpty (Key, a) -> Ordering)
-> (NEIntMap a -> NonEmpty (Key, a))
-> NEIntMap a
-> NEIntMap a
-> Ordering
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
    < :: NEIntMap a -> NEIntMap a -> Bool
(<)     = NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool
forall a. Ord a => a -> a -> Bool
(<) (NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool)
-> (NEIntMap a -> NonEmpty (Key, a))
-> NEIntMap a
-> NEIntMap a
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
    > :: NEIntMap a -> NEIntMap a -> Bool
(>)     = NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool
forall a. Ord a => a -> a -> Bool
(>) (NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool)
-> (NEIntMap a -> NonEmpty (Key, a))
-> NEIntMap a
-> NEIntMap a
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
    <= :: NEIntMap a -> NEIntMap a -> Bool
(<=)    = NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool
forall a. Ord a => a -> a -> Bool
(<=) (NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool)
-> (NEIntMap a -> NonEmpty (Key, a))
-> NEIntMap a
-> NEIntMap a
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
    >= :: NEIntMap a -> NEIntMap a -> Bool
(>=)    = NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool
forall a. Ord a => a -> a -> Bool
(>=) (NonEmpty (Key, a) -> NonEmpty (Key, a) -> Bool)
-> (NEIntMap a -> NonEmpty (Key, a))
-> NEIntMap a
-> NEIntMap a
-> Bool
forall b c a. (b -> b -> c) -> (a -> b) -> a -> a -> c
`on` NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
instance Eq1 NEIntMap where
    liftEq :: (a -> b -> Bool) -> NEIntMap a -> NEIntMap b -> Bool
liftEq a -> b -> Bool
eq NEIntMap a
m1 NEIntMap b
m2 = IntMap a -> Key
forall a. IntMap a -> Key
M.size (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
neimIntMap NEIntMap a
m1) Key -> Key -> Bool
forall a. Eq a => a -> a -> Bool
== IntMap b -> Key
forall a. IntMap a -> Key
M.size (NEIntMap b -> IntMap b
forall a. NEIntMap a -> IntMap a
neimIntMap NEIntMap b
m2)
                   Bool -> Bool -> Bool
&& ((Key, a) -> (Key, b) -> Bool)
-> NonEmpty (Key, a) -> NonEmpty (Key, b) -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq ((a -> b -> Bool) -> (Key, a) -> (Key, b) -> Bool
forall (f :: * -> *) a b.
Eq1 f =>
(a -> b -> Bool) -> f a -> f b -> Bool
liftEq a -> b -> Bool
eq) (NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap a
m1) (NEIntMap b -> NonEmpty (Key, b)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap b
m2)
instance Ord1 NEIntMap where
    liftCompare :: (a -> b -> Ordering) -> NEIntMap a -> NEIntMap b -> Ordering
liftCompare a -> b -> Ordering
cmp NEIntMap a
m NEIntMap b
n =
        ((Key, a) -> (Key, b) -> Ordering)
-> NonEmpty (Key, a) -> NonEmpty (Key, b) -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare ((a -> b -> Ordering) -> (Key, a) -> (Key, b) -> Ordering
forall (f :: * -> *) a b.
Ord1 f =>
(a -> b -> Ordering) -> f a -> f b -> Ordering
liftCompare a -> b -> Ordering
cmp) (NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap a
m) (NEIntMap b -> NonEmpty (Key, b)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap b
n)
instance Show1 NEIntMap where
    liftShowsPrec :: (Key -> a -> ShowS) -> ([a] -> ShowS) -> Key -> NEIntMap a -> ShowS
liftShowsPrec Key -> a -> ShowS
sp [a] -> ShowS
sl Key
d NEIntMap a
m =
        (Key -> NonEmpty (Key, a) -> ShowS)
-> String -> Key -> NonEmpty (Key, a) -> ShowS
forall a. (Key -> a -> ShowS) -> String -> Key -> a -> ShowS
showsUnaryWith ((Key -> (Key, a) -> ShowS)
-> ([(Key, a)] -> ShowS) -> Key -> NonEmpty (Key, a) -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Key -> a -> ShowS) -> ([a] -> ShowS) -> Key -> f a -> ShowS
liftShowsPrec Key -> (Key, a) -> ShowS
sp' [(Key, a)] -> ShowS
sl') String
"fromList" Key
d (NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap a
m)
      where
        sp' :: Key -> (Key, a) -> ShowS
sp' = (Key -> a -> ShowS) -> ([a] -> ShowS) -> Key -> (Key, a) -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Key -> a -> ShowS) -> ([a] -> ShowS) -> Key -> f a -> ShowS
liftShowsPrec Key -> a -> ShowS
sp [a] -> ShowS
sl
        sl' :: [(Key, a)] -> ShowS
sl' = (Key -> a -> ShowS) -> ([a] -> ShowS) -> [(Key, a)] -> ShowS
forall (f :: * -> *) a.
Show1 f =>
(Key -> a -> ShowS) -> ([a] -> ShowS) -> [f a] -> ShowS
liftShowList Key -> a -> ShowS
sp [a] -> ShowS
sl
instance Read1 NEIntMap where
    liftReadsPrec :: (Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (NEIntMap a)
liftReadsPrec Key -> ReadS a
rp ReadS [a]
rl = (String -> ReadS (NEIntMap a)) -> Key -> ReadS (NEIntMap a)
forall a. (String -> ReadS a) -> Key -> ReadS a
readsData ((String -> ReadS (NEIntMap a)) -> Key -> ReadS (NEIntMap a))
-> (String -> ReadS (NEIntMap a)) -> Key -> ReadS (NEIntMap a)
forall a b. (a -> b) -> a -> b
$
        (Key -> ReadS (NonEmpty (Key, a)))
-> String
-> (NonEmpty (Key, a) -> NEIntMap a)
-> String
-> ReadS (NEIntMap a)
forall a t.
(Key -> ReadS a) -> String -> (a -> t) -> String -> ReadS t
readsUnaryWith ((Key -> ReadS (Key, a))
-> ReadS [(Key, a)] -> Key -> ReadS (NonEmpty (Key, a))
forall (f :: * -> *) a.
Read1 f =>
(Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (f a)
liftReadsPrec Key -> ReadS (Key, a)
rp' ReadS [(Key, a)]
rl') String
"fromList" NonEmpty (Key, a) -> NEIntMap a
forall a. NonEmpty (Key, a) -> NEIntMap a
fromList
      where
        rp' :: Key -> ReadS (Key, a)
rp' = (Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (Key, a)
forall (f :: * -> *) a.
Read1 f =>
(Key -> ReadS a) -> ReadS [a] -> Key -> ReadS (f a)
liftReadsPrec Key -> ReadS a
rp ReadS [a]
rl
        rl' :: ReadS [(Key, a)]
rl' = (Key -> ReadS a) -> ReadS [a] -> ReadS [(Key, a)]
forall (f :: * -> *) a.
Read1 f =>
(Key -> ReadS a) -> ReadS [a] -> ReadS [f a]
liftReadList Key -> ReadS a
rp ReadS [a]
rl
instance Read e => Read (NEIntMap e) where
    readPrec :: ReadPrec (NEIntMap e)
readPrec = ReadPrec (NEIntMap e) -> ReadPrec (NEIntMap e)
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (NEIntMap e) -> ReadPrec (NEIntMap e))
-> ReadPrec (NEIntMap e) -> ReadPrec (NEIntMap e)
forall a b. (a -> b) -> a -> b
$ Key -> ReadPrec (NEIntMap e) -> ReadPrec (NEIntMap e)
forall a. Key -> ReadPrec a -> ReadPrec a
prec Key
10 (ReadPrec (NEIntMap e) -> ReadPrec (NEIntMap e))
-> ReadPrec (NEIntMap e) -> ReadPrec (NEIntMap e)
forall a b. (a -> b) -> a -> b
$ do
      Ident String
"fromList" <- ReadPrec Lexeme
lexP
      NonEmpty (Key, e)
xs <- ReadPrec (NonEmpty (Key, e)) -> ReadPrec (NonEmpty (Key, e))
forall a. ReadPrec a -> ReadPrec a
parens (ReadPrec (NonEmpty (Key, e)) -> ReadPrec (NonEmpty (Key, e)))
-> (ReadPrec (NonEmpty (Key, e)) -> ReadPrec (NonEmpty (Key, e)))
-> ReadPrec (NonEmpty (Key, e))
-> ReadPrec (NonEmpty (Key, e))
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> ReadPrec (NonEmpty (Key, e)) -> ReadPrec (NonEmpty (Key, e))
forall a. Key -> ReadPrec a -> ReadPrec a
prec Key
10 (ReadPrec (NonEmpty (Key, e)) -> ReadPrec (NonEmpty (Key, e)))
-> ReadPrec (NonEmpty (Key, e)) -> ReadPrec (NonEmpty (Key, e))
forall a b. (a -> b) -> a -> b
$ ReadPrec (NonEmpty (Key, e))
forall a. Read a => ReadPrec a
readPrec
      NEIntMap e -> ReadPrec (NEIntMap e)
forall (m :: * -> *) a. Monad m => a -> m a
return (NonEmpty (Key, e) -> NEIntMap e
forall a. NonEmpty (Key, a) -> NEIntMap a
fromList NonEmpty (Key, e)
xs)
    readListPrec :: ReadPrec [NEIntMap e]
readListPrec = ReadPrec [NEIntMap e]
forall a. Read a => ReadPrec [a]
readListPrecDefault
instance Show a => Show (NEIntMap a) where
    showsPrec :: Key -> NEIntMap a -> ShowS
showsPrec Key
d NEIntMap a
m  = Bool -> ShowS -> ShowS
showParen (Key
d Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
> Key
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
      String -> ShowS
showString String
"fromList (" ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NonEmpty (Key, a) -> ShowS
forall a. Show a => a -> ShowS
shows (NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap a
m) ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> ShowS
showString String
")"
instance NFData a => NFData (NEIntMap a) where
    rnf :: NEIntMap a -> ()
rnf (NEIntMap Key
k a
v IntMap a
a) = Key -> ()
forall a. NFData a => a -> ()
rnf Key
k () -> () -> ()
`seq` a -> ()
forall a. NFData a => a -> ()
rnf a
v () -> () -> ()
`seq` IntMap a -> ()
forall a. NFData a => a -> ()
rnf IntMap a
a
instance Data a => Data (NEIntMap a) where
  gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> NEIntMap a -> c (NEIntMap a)
gfoldl forall d b. Data d => c (d -> b) -> d -> c b
f forall g. g -> c g
z NEIntMap a
im = (NonEmpty (Key, a) -> NEIntMap a)
-> c (NonEmpty (Key, a) -> NEIntMap a)
forall g. g -> c g
z NonEmpty (Key, a) -> NEIntMap a
forall a. NonEmpty (Key, a) -> NEIntMap a
fromList c (NonEmpty (Key, a) -> NEIntMap a)
-> NonEmpty (Key, a) -> c (NEIntMap a)
forall d b. Data d => c (d -> b) -> d -> c b
`f` NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList NEIntMap a
im
  toConstr :: NEIntMap a -> Constr
toConstr NEIntMap a
_     = Constr
fromListConstr
  gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (NEIntMap a)
gunfold forall b r. Data b => c (b -> r) -> c r
k forall r. r -> c r
z Constr
c  = case Constr -> Key
constrIndex Constr
c of
    Key
1 -> c (NonEmpty (Key, a) -> NEIntMap a) -> c (NEIntMap a)
forall b r. Data b => c (b -> r) -> c r
k ((NonEmpty (Key, a) -> NEIntMap a)
-> c (NonEmpty (Key, a) -> NEIntMap a)
forall r. r -> c r
z NonEmpty (Key, a) -> NEIntMap a
forall a. NonEmpty (Key, a) -> NEIntMap a
fromList)
    Key
_ -> String -> c (NEIntMap a)
forall a. HasCallStack => String -> a
error String
"gunfold"
  dataTypeOf :: NEIntMap a -> DataType
dataTypeOf NEIntMap a
_   = DataType
intMapDataType
  dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (NEIntMap a))
dataCast1 forall d. Data d => c (t d)
f    = c (t a) -> Maybe (c (NEIntMap a))
forall k1 k2 (c :: k1 -> *) (t :: k2 -> k1) (t' :: k2 -> k1)
       (a :: k2).
(Typeable t, Typeable t') =>
c (t a) -> Maybe (c (t' a))
gcast1 c (t a)
forall d. Data d => c (t d)
f
fromListConstr :: Constr
fromListConstr :: Constr
fromListConstr = DataType -> String -> [String] -> Fixity -> Constr
mkConstr DataType
intMapDataType String
"fromList" [] Fixity
Prefix
intMapDataType :: DataType
intMapDataType :: DataType
intMapDataType = String -> [Constr] -> DataType
mkDataType String
"Data.IntMap.NonEmpty.Internal.NEIntMap" [Constr
fromListConstr]
instance A.ToJSON a => A.ToJSON (NEIntMap a) where
    toJSON :: NEIntMap a -> Value
toJSON     = IntMap a -> Value
forall a. ToJSON a => a -> Value
A.toJSON (IntMap a -> Value)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> Value
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap
    toEncoding :: NEIntMap a -> Encoding
toEncoding = IntMap a -> Encoding
forall a. ToJSON a => a -> Encoding
A.toEncoding (IntMap a -> Encoding)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> Encoding
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap
instance A.FromJSON a => A.FromJSON (NEIntMap a) where
    parseJSON :: Value -> Parser (NEIntMap a)
parseJSON = Parser (NEIntMap a)
-> (NEIntMap a -> Parser (NEIntMap a))
-> IntMap a
-> Parser (NEIntMap a)
forall r a. r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty (String -> Parser (NEIntMap a)
forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
err) NEIntMap a -> Parser (NEIntMap a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure
            (IntMap a -> Parser (NEIntMap a))
-> (Value -> Parser (IntMap a)) -> Value -> Parser (NEIntMap a)
forall (m :: * -> *) b c a.
Monad m =>
(b -> m c) -> (a -> m b) -> a -> m c
<=< Value -> Parser (IntMap a)
forall a. FromJSON a => Value -> Parser a
A.parseJSON
      where
        err :: String
err = String
"NEIntMap: Non-empty map expected, but empty map found"
instance Alt NEIntMap where
    <!> :: NEIntMap a -> NEIntMap a -> NEIntMap a
(<!>) = NEIntMap a -> NEIntMap a -> NEIntMap a
forall a. NEIntMap a -> NEIntMap a -> NEIntMap a
union
foldr :: (a -> b -> b) -> b -> NEIntMap a -> b
foldr :: (a -> b -> b) -> b -> NEIntMap a -> b
foldr a -> b -> b
f b
z (NEIntMap Key
_ a
v IntMap a
m) = a
v a -> b -> b
`f` (a -> b -> b) -> b -> IntMap a -> b
forall a b. (a -> b -> b) -> b -> IntMap a -> b
M.foldr a -> b -> b
f b
z IntMap a
m
{-# INLINE foldr #-}
foldr' :: (a -> b -> b) -> b -> NEIntMap a -> b
foldr' :: (a -> b -> b) -> b -> NEIntMap a -> b
foldr' a -> b -> b
f b
z (NEIntMap Key
_ a
v IntMap a
m) = a
v a -> b -> b
`f` b
y
  where
    !y :: b
y = (a -> b -> b) -> b -> IntMap a -> b
forall a b. (a -> b -> b) -> b -> IntMap a -> b
M.foldr' a -> b -> b
f b
z IntMap a
m
{-# INLINE foldr' #-}
foldr1 :: (a -> a -> a) -> NEIntMap a -> a
foldr1 :: (a -> a -> a) -> NEIntMap a -> a
foldr1 a -> a -> a
f (NEIntMap Key
_ a
v IntMap a
m) = a -> ((a, IntMap a) -> a) -> Maybe (a, IntMap a) -> a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe a
v (a -> a -> a
f a
v (a -> a) -> ((a, IntMap a) -> a) -> (a, IntMap a) -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> IntMap a -> a) -> (a, IntMap a) -> a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry ((a -> a -> a) -> a -> IntMap a -> a
forall a b. (a -> b -> b) -> b -> IntMap a -> b
M.foldr a -> a -> a
f))
                       (Maybe (a, IntMap a) -> a)
-> (IntMap a -> Maybe (a, IntMap a)) -> IntMap a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe (a, IntMap a)
forall a. IntMap a -> Maybe (a, IntMap a)
M.maxView
                       (IntMap a -> a) -> IntMap a -> a
forall a b. (a -> b) -> a -> b
$ IntMap a
m
{-# INLINE foldr1 #-}
foldl :: (a -> b -> a) -> a -> NEIntMap b -> a
foldl :: (a -> b -> a) -> a -> NEIntMap b -> a
foldl a -> b -> a
f a
z (NEIntMap Key
_ b
v IntMap b
m) = (a -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> b -> a) -> a -> IntMap b -> a
M.foldl a -> b -> a
f (a -> b -> a
f a
z b
v) IntMap b
m
{-# INLINE foldl #-}
foldl' :: (a -> b -> a) -> a -> NEIntMap b -> a
foldl' :: (a -> b -> a) -> a -> NEIntMap b -> a
foldl' a -> b -> a
f a
z (NEIntMap Key
_ b
v IntMap b
m) = (a -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> b -> a) -> a -> IntMap b -> a
M.foldl' a -> b -> a
f a
x IntMap b
m
  where
    !x :: a
x = a -> b -> a
f a
z b
v
{-# INLINE foldl' #-}
foldl1 :: (a -> a -> a) -> NEIntMap a -> a
foldl1 :: (a -> a -> a) -> NEIntMap a -> a
foldl1 a -> a -> a
f (NEIntMap Key
_ a
v IntMap a
m) = (a -> a -> a) -> a -> IntMap a -> a
forall a b. (a -> b -> a) -> a -> IntMap b -> a
M.foldl a -> a -> a
f a
v IntMap a
m
{-# INLINE foldl1 #-}
foldMapWithKey
    :: Semigroup m
    => (Key -> a -> m)
    -> NEIntMap a
    -> m
foldMapWithKey :: (Key -> a -> m) -> NEIntMap a -> m
foldMapWithKey Key -> a -> m
f = ((Key, a) -> m) -> NonEmpty (Key, a) -> m
forall (t :: * -> *) m a.
(Foldable1 t, Semigroup m) =>
(a -> m) -> t a -> m
F1.foldMap1 ((Key -> a -> m) -> (Key, a) -> m
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry Key -> a -> m
f) (NonEmpty (Key, a) -> m)
-> (NEIntMap a -> NonEmpty (Key, a)) -> NEIntMap a -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> NonEmpty (Key, a)
forall a. NEIntMap a -> NonEmpty (Key, a)
toList
{-# INLINE foldMapWithKey #-}
map :: (a -> b) -> NEIntMap a -> NEIntMap b
map :: (a -> b) -> NEIntMap a -> NEIntMap b
map a -> b
f (NEIntMap Key
k0 a
v IntMap a
m) = Key -> b -> IntMap b -> NEIntMap b
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 (a -> b
f a
v) ((a -> b) -> IntMap a -> IntMap b
forall a b. (a -> b) -> IntMap a -> IntMap b
M.map a -> b
f IntMap a
m)
{-# NOINLINE [1] map #-}
{-# RULES
"map/map" forall f g xs . map f (map g xs) = map (f . g) xs
 #-}
{-# RULES
"map/coerce" map coerce = coerce
 #-}
union
    :: NEIntMap a
    -> NEIntMap a
    -> NEIntMap a
union :: NEIntMap a -> NEIntMap a -> NEIntMap a
union n1 :: NEIntMap a
n1@(NEIntMap Key
k1 a
v1 IntMap a
m1) n2 :: NEIntMap a
n2@(NEIntMap Key
k2 a
v2 IntMap a
m2) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k1 Key
k2 of
    Ordering
LT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k1 a
v1 (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
M.union IntMap a
m1 (IntMap a -> IntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> IntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n2
    Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k1 a
v1 (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
M.union IntMap a
m1         (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m2
    Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k2 a
v2 (IntMap a -> NEIntMap a)
-> (IntMap a -> IntMap a) -> IntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> IntMap a -> IntMap a
forall a. IntMap a -> IntMap a -> IntMap a
M.union (NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap NEIntMap a
n1) (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ IntMap a
m2
{-# INLINE union #-}
unions
    :: Foldable1 f
    => f (NEIntMap a)
    -> NEIntMap a
unions :: f (NEIntMap a) -> NEIntMap a
unions (f (NEIntMap a) -> NonEmpty (NEIntMap a)
forall (t :: * -> *) a. Foldable1 t => t a -> NonEmpty a
F1.toNonEmpty->(NEIntMap a
m :| [NEIntMap a]
ms)) = (NEIntMap a -> NEIntMap a -> NEIntMap a)
-> NEIntMap a -> [NEIntMap a] -> NEIntMap a
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
F.foldl' NEIntMap a -> NEIntMap a -> NEIntMap a
forall a. NEIntMap a -> NEIntMap a -> NEIntMap a
union NEIntMap a
m [NEIntMap a]
ms
{-# INLINE unions #-}
elems :: NEIntMap a -> NonEmpty a
elems :: NEIntMap a -> NonEmpty a
elems (NEIntMap Key
_ a
v IntMap a
m) = a
v a -> [a] -> NonEmpty a
forall a. a -> [a] -> NonEmpty a
:| IntMap a -> [a]
forall a. IntMap a -> [a]
M.elems IntMap a
m
{-# INLINE elems #-}
size :: NEIntMap a -> Int
size :: NEIntMap a -> Key
size (NEIntMap Key
_ a
_ IntMap a
m) = Key
1 Key -> Key -> Key
forall a. Num a => a -> a -> a
+ IntMap a -> Key
forall a. IntMap a -> Key
M.size IntMap a
m
{-# INLINE size #-}
toMap :: NEIntMap a -> IntMap a
toMap :: NEIntMap a -> IntMap a
toMap (NEIntMap Key
k a
v IntMap a
m) = Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
insertMinMap Key
k a
v IntMap a
m
{-# INLINE toMap #-}
traverseWithKey
    :: Applicative t
    => (Key -> a -> t b)
    -> NEIntMap a
    -> t (NEIntMap b)
traverseWithKey :: (Key -> a -> t b) -> NEIntMap a -> t (NEIntMap b)
traverseWithKey Key -> a -> t b
f (NEIntMap Key
k a
v IntMap a
m0) =
        Key -> b -> IntMap b -> NEIntMap b
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k (b -> IntMap b -> NEIntMap b) -> t b -> t (IntMap b -> NEIntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> t b
f Key
k a
v
                   t (IntMap b -> NEIntMap b) -> t (IntMap b) -> t (NEIntMap b)
forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (Key -> a -> t b) -> IntMap a -> t (IntMap b)
forall (t :: * -> *) a b.
Applicative t =>
(Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseMapWithKey Key -> a -> t b
f IntMap a
m0
{-# INLINE traverseWithKey #-}
traverseWithKey1
    :: Apply t
    => (Key -> a -> t b)
    -> NEIntMap a
    -> t (NEIntMap b)
traverseWithKey1 :: (Key -> a -> t b) -> NEIntMap a -> t (NEIntMap b)
traverseWithKey1 Key -> a -> t b
f (NEIntMap Key
k0 a
v IntMap a
m0) = case MaybeApply t (IntMap b) -> Either (t (IntMap b)) (IntMap b)
forall (f :: * -> *) a. MaybeApply f a -> Either (f a) a
runMaybeApply MaybeApply t (IntMap b)
m1 of
    Left  t (IntMap b)
m2 -> Key -> b -> IntMap b -> NEIntMap b
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 (b -> IntMap b -> NEIntMap b) -> t b -> t (IntMap b -> NEIntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> t b
f Key
k0 a
v t (IntMap b -> NEIntMap b) -> t (IntMap b) -> t (NEIntMap b)
forall (f :: * -> *) a b. Apply f => f (a -> b) -> f a -> f b
<.> t (IntMap b)
m2
    Right IntMap b
m2 -> (b -> IntMap b -> NEIntMap b) -> IntMap b -> b -> NEIntMap b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> b -> IntMap b -> NEIntMap b
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0) IntMap b
m2 (b -> NEIntMap b) -> t b -> t (NEIntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> t b
f Key
k0 a
v
  where
    m1 :: MaybeApply t (IntMap b)
m1 = (Key -> a -> MaybeApply t b) -> IntMap a -> MaybeApply t (IntMap b)
forall (t :: * -> *) a b.
Applicative t =>
(Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseMapWithKey (\Key
k -> Either (t b) b -> MaybeApply t b
forall (f :: * -> *) a. Either (f a) a -> MaybeApply f a
MaybeApply (Either (t b) b -> MaybeApply t b)
-> (a -> Either (t b) b) -> a -> MaybeApply t b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. t b -> Either (t b) b
forall a b. a -> Either a b
Left (t b -> Either (t b) b) -> (a -> t b) -> a -> Either (t b) b
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Key -> a -> t b
f Key
k) IntMap a
m0
{-# INLINABLE traverseWithKey1 #-}
toList :: NEIntMap a -> NonEmpty (Key, a)
toList :: NEIntMap a -> NonEmpty (Key, a)
toList (NEIntMap Key
k a
v IntMap a
m) = (Key
k,a
v) (Key, a) -> [(Key, a)] -> NonEmpty (Key, a)
forall a. a -> [a] -> NonEmpty a
:| IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
M.toList IntMap a
m
{-# INLINE toList #-}
nonEmptyMap :: IntMap a -> Maybe (NEIntMap a)
nonEmptyMap :: IntMap a -> Maybe (NEIntMap a)
nonEmptyMap = ((((Key, a), IntMap a) -> NEIntMap a)
-> Maybe ((Key, a), IntMap a) -> Maybe (NEIntMap a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap ((((Key, a), IntMap a) -> NEIntMap a)
 -> Maybe ((Key, a), IntMap a) -> Maybe (NEIntMap a))
-> ((Key -> a -> IntMap a -> NEIntMap a)
    -> ((Key, a), IntMap a) -> NEIntMap a)
-> (Key -> a -> IntMap a -> NEIntMap a)
-> Maybe ((Key, a), IntMap a)
-> Maybe (NEIntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key, a) -> IntMap a -> NEIntMap a)
-> ((Key, a), IntMap a) -> NEIntMap a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry (((Key, a) -> IntMap a -> NEIntMap a)
 -> ((Key, a), IntMap a) -> NEIntMap a)
-> ((Key -> a -> IntMap a -> NEIntMap a)
    -> (Key, a) -> IntMap a -> NEIntMap a)
-> (Key -> a -> IntMap a -> NEIntMap a)
-> ((Key, a), IntMap a)
-> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key -> a -> IntMap a -> NEIntMap a)
-> (Key, a) -> IntMap a -> NEIntMap a
forall a b c. (a -> b -> c) -> (a, b) -> c
uncurry) Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap (Maybe ((Key, a), IntMap a) -> Maybe (NEIntMap a))
-> (IntMap a -> Maybe ((Key, a), IntMap a))
-> IntMap a
-> Maybe (NEIntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe ((Key, a), IntMap a)
forall a. IntMap a -> Maybe ((Key, a), IntMap a)
M.minViewWithKey
{-# INLINE nonEmptyMap #-}
withNonEmpty
    :: r                    
    -> (NEIntMap a -> r)     
    -> IntMap a
    -> r
withNonEmpty :: r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty r
def NEIntMap a -> r
f = r -> (NEIntMap a -> r) -> Maybe (NEIntMap a) -> r
forall b a. b -> (a -> b) -> Maybe a -> b
maybe r
def NEIntMap a -> r
f (Maybe (NEIntMap a) -> r)
-> (IntMap a -> Maybe (NEIntMap a)) -> IntMap a -> r
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> Maybe (NEIntMap a)
forall a. IntMap a -> Maybe (NEIntMap a)
nonEmptyMap
{-# INLINE withNonEmpty #-}
fromList :: NonEmpty (Key, a) -> NEIntMap a
fromList :: NonEmpty (Key, a) -> NEIntMap a
fromList ((Key
k, a
v) :| [(Key, a)]
xs) = NEIntMap a -> (NEIntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall r a. r -> (NEIntMap a -> r) -> IntMap a -> r
withNonEmpty (Key -> a -> NEIntMap a
forall a. Key -> a -> NEIntMap a
singleton Key
k a
v) ((a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
forall a. (a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
insertWith ((a -> a) -> a -> a -> a
forall a b. a -> b -> a
const a -> a
forall a. a -> a
id) Key
k a
v)
                        (IntMap a -> NEIntMap a)
-> ([(Key, a)] -> IntMap a) -> [(Key, a)] -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, a)] -> IntMap a
forall a. [(Key, a)] -> IntMap a
M.fromList
                        ([(Key, a)] -> NEIntMap a) -> [(Key, a)] -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ [(Key, a)]
xs
{-# INLINE fromList #-}
singleton :: Key -> a -> NEIntMap a
singleton :: Key -> a -> NEIntMap a
singleton Key
k a
v = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k a
v IntMap a
forall a. IntMap a
M.empty
{-# INLINE singleton #-}
insertWith
    :: (a -> a -> a)
    -> Key
    -> a
    -> NEIntMap a
    -> NEIntMap a
insertWith :: (a -> a -> a) -> Key -> a -> NEIntMap a -> NEIntMap a
insertWith a -> a -> a
f Key
k a
v n :: NEIntMap a
n@(NEIntMap Key
k0 a
v0 IntMap a
m) = case Key -> Key -> Ordering
forall a. Ord a => a -> a -> Ordering
compare Key
k Key
k0 of
    Ordering
LT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k  a
v        (IntMap a -> NEIntMap a)
-> (NEIntMap a -> IntMap a) -> NEIntMap a -> NEIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> IntMap a
forall a. NEIntMap a -> IntMap a
toMap            (NEIntMap a -> NEIntMap a) -> NEIntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ NEIntMap a
n
    Ordering
EQ -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k  (a -> a -> a
f a
v a
v0) IntMap a
m
    Ordering
GT -> Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 a
v0       (IntMap a -> NEIntMap a) -> IntMap a -> NEIntMap a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> Key -> a -> IntMap a -> IntMap a
M.insertWith a -> a -> a
f Key
k a
v IntMap a
m
{-# INLINE insertWith #-}
instance Semigroup (NEIntMap a) where
    <> :: NEIntMap a -> NEIntMap a -> NEIntMap a
(<>) = NEIntMap a -> NEIntMap a -> NEIntMap a
forall a. NEIntMap a -> NEIntMap a -> NEIntMap a
union
    {-# INLINE (<>) #-}
    sconcat :: NonEmpty (NEIntMap a) -> NEIntMap a
sconcat = NonEmpty (NEIntMap a) -> NEIntMap a
forall (f :: * -> *) a. Foldable1 f => f (NEIntMap a) -> NEIntMap a
unions
    {-# INLINE sconcat #-}
instance Functor NEIntMap where
    fmap :: (a -> b) -> NEIntMap a -> NEIntMap b
fmap = (a -> b) -> NEIntMap a -> NEIntMap b
forall a b. (a -> b) -> NEIntMap a -> NEIntMap b
map
    {-# INLINE fmap #-}
    a
x <$ :: a -> NEIntMap b -> NEIntMap a
<$ NEIntMap Key
k b
_ IntMap b
m = Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k a
x (a
x a -> IntMap b -> IntMap a
forall (f :: * -> *) a b. Functor f => a -> f b -> f a
<$ IntMap b
m)
    {-# INLINE (<$) #-}
instance Invariant NEIntMap where
    invmap :: (a -> b) -> (b -> a) -> NEIntMap a -> NEIntMap b
invmap a -> b
f b -> a
_ = (a -> b) -> NEIntMap a -> NEIntMap b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap a -> b
f
    {-# INLINE invmap #-}
instance Foldable NEIntMap where
#if MIN_VERSION_base(4,11,0)
    fold :: NEIntMap m -> m
fold      (NEIntMap Key
_ m
v IntMap m
m) = m
v m -> m -> m
forall a. Semigroup a => a -> a -> a
<> [m] -> m
forall (t :: * -> *) m. (Foldable t, Monoid m) => t m -> m
F.fold (IntMap m -> [m]
forall a. IntMap a -> [a]
M.elems IntMap m
m)
    {-# INLINE fold #-}
    foldMap :: (a -> m) -> NEIntMap a -> m
foldMap a -> m
f (NEIntMap Key
_ a
v IntMap a
m) = a -> m
f a
v m -> m -> m
forall a. Semigroup a => a -> a -> a
<> (a -> m) -> [a] -> m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap a -> m
f (IntMap a -> [a]
forall a. IntMap a -> [a]
M.elems IntMap a
m)
    {-# INLINE foldMap #-}
#else
    fold      (NEIntMap _ v m) = v `mappend` F.fold (M.elems m)
    {-# INLINE fold #-}
    foldMap f (NEIntMap _ v m) = f v `mappend` foldMap f (M.elems m)
    {-# INLINE foldMap #-}
#endif
    foldr :: (a -> b -> b) -> b -> NEIntMap a -> b
foldr   = (a -> b -> b) -> b -> NEIntMap a -> b
forall a b. (a -> b -> b) -> b -> NEIntMap a -> b
foldr
    {-# INLINE foldr #-}
    foldr' :: (a -> b -> b) -> b -> NEIntMap a -> b
foldr'  = (a -> b -> b) -> b -> NEIntMap a -> b
forall a b. (a -> b -> b) -> b -> NEIntMap a -> b
foldr'
    {-# INLINE foldr' #-}
    foldr1 :: (a -> a -> a) -> NEIntMap a -> a
foldr1  = (a -> a -> a) -> NEIntMap a -> a
forall a. (a -> a -> a) -> NEIntMap a -> a
foldr1
    {-# INLINE foldr1 #-}
    foldl :: (b -> a -> b) -> b -> NEIntMap a -> b
foldl   = (b -> a -> b) -> b -> NEIntMap a -> b
forall b a. (b -> a -> b) -> b -> NEIntMap a -> b
foldl
    {-# INLINE foldl #-}
    foldl' :: (b -> a -> b) -> b -> NEIntMap a -> b
foldl'  = (b -> a -> b) -> b -> NEIntMap a -> b
forall b a. (b -> a -> b) -> b -> NEIntMap a -> b
foldl'
    {-# INLINE foldl' #-}
    foldl1 :: (a -> a -> a) -> NEIntMap a -> a
foldl1  = (a -> a -> a) -> NEIntMap a -> a
forall a. (a -> a -> a) -> NEIntMap a -> a
foldl1
    {-# INLINE foldl1 #-}
    null :: NEIntMap a -> Bool
null NEIntMap a
_  = Bool
False
    {-# INLINE null #-}
    length :: NEIntMap a -> Key
length  = NEIntMap a -> Key
forall a. NEIntMap a -> Key
size
    {-# INLINE length #-}
    elem :: a -> NEIntMap a -> Bool
elem a
x (NEIntMap Key
_ a
v IntMap a
m) = a -> IntMap a -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
F.elem a
x IntMap a
m
                           Bool -> Bool -> Bool
|| a
x a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
v
    {-# INLINE elem #-}
    
    toList :: NEIntMap a -> [a]
toList  = NonEmpty a -> [a]
forall (t :: * -> *) a. Foldable t => t a -> [a]
F.toList (NonEmpty a -> [a])
-> (NEIntMap a -> NonEmpty a) -> NEIntMap a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. NEIntMap a -> NonEmpty a
forall a. NEIntMap a -> NonEmpty a
elems
    {-# INLINE toList #-}
instance Traversable NEIntMap where
    traverse :: (a -> f b) -> NEIntMap a -> f (NEIntMap b)
traverse a -> f b
f = (Key -> a -> f b) -> NEIntMap a -> f (NEIntMap b)
forall (t :: * -> *) a b.
Applicative t =>
(Key -> a -> t b) -> NEIntMap a -> t (NEIntMap b)
traverseWithKey ((a -> f b) -> Key -> a -> f b
forall a b. a -> b -> a
const a -> f b
f)
    {-# INLINE traverse #-}
instance Foldable1 NEIntMap where
#if MIN_VERSION_base(4,11,0)
    fold1 :: NEIntMap m -> m
fold1 (NEIntMap Key
_ m
v IntMap m
m) = m -> (m -> m) -> Maybe m -> m
forall b a. b -> (a -> b) -> Maybe a -> b
maybe m
v (m
v m -> m -> m
forall a. Semigroup a => a -> a -> a
<>)
                           (Maybe m -> m) -> (IntMap m -> Maybe m) -> IntMap m -> m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (m -> Maybe m) -> [m] -> Maybe m
forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
F.foldMap m -> Maybe m
forall a. a -> Maybe a
Just
                           ([m] -> Maybe m) -> (IntMap m -> [m]) -> IntMap m -> Maybe m
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap m -> [m]
forall a. IntMap a -> [a]
M.elems
                           (IntMap m -> m) -> IntMap m -> m
forall a b. (a -> b) -> a -> b
$ IntMap m
m
#else
    fold1 (NEIntMap _ v m) = option v (v <>)
                           . F.foldMap (Option . Just)
                           . M.elems
                           $ m
#endif
    {-# INLINE fold1 #-}
    foldMap1 :: (a -> m) -> NEIntMap a -> m
foldMap1 a -> m
f = (Key -> a -> m) -> NEIntMap a -> m
forall m a. Semigroup m => (Key -> a -> m) -> NEIntMap a -> m
foldMapWithKey ((a -> m) -> Key -> a -> m
forall a b. a -> b -> a
const a -> m
f)
    {-# INLINE foldMap1 #-}
    toNonEmpty :: NEIntMap a -> NonEmpty a
toNonEmpty = NEIntMap a -> NonEmpty a
forall a. NEIntMap a -> NonEmpty a
elems
    {-# INLINE toNonEmpty #-}
instance Traversable1 NEIntMap where
    traverse1 :: (a -> f b) -> NEIntMap a -> f (NEIntMap b)
traverse1 a -> f b
f = (Key -> a -> f b) -> NEIntMap a -> f (NEIntMap b)
forall (t :: * -> *) a b.
Apply t =>
(Key -> a -> t b) -> NEIntMap a -> t (NEIntMap b)
traverseWithKey1 ((a -> f b) -> Key -> a -> f b
forall a b. a -> b -> a
const a -> f b
f)
    {-# INLINE traverse1 #-}
instance Comonad NEIntMap where
    extract :: NEIntMap a -> a
extract = NEIntMap a -> a
forall a. NEIntMap a -> a
neimV0
    {-# INLINE extract #-}
    
    
    duplicate :: NEIntMap a -> NEIntMap (NEIntMap a)
duplicate n0 :: NEIntMap a
n0@(NEIntMap Key
k0 a
_ IntMap a
m0) = Key -> NEIntMap a -> IntMap (NEIntMap a) -> NEIntMap (NEIntMap a)
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k0 NEIntMap a
n0
                                    (IntMap (NEIntMap a) -> NEIntMap (NEIntMap a))
-> (IntMap a -> IntMap (NEIntMap a))
-> IntMap a
-> NEIntMap (NEIntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, NEIntMap a)] -> IntMap (NEIntMap a)
forall a. [(Key, a)] -> IntMap a
M.fromDistinctAscList
                                    ([(Key, NEIntMap a)] -> IntMap (NEIntMap a))
-> (IntMap a -> [(Key, NEIntMap a)])
-> IntMap a
-> IntMap (NEIntMap a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a, [(Key, NEIntMap a)]) -> [(Key, NEIntMap a)]
forall a b. (a, b) -> b
snd
                                    ((IntMap a, [(Key, NEIntMap a)]) -> [(Key, NEIntMap a)])
-> (IntMap a -> (IntMap a, [(Key, NEIntMap a)]))
-> IntMap a
-> [(Key, NEIntMap a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (IntMap a -> (Key, a) -> (IntMap a, (Key, NEIntMap a)))
-> IntMap a -> [(Key, a)] -> (IntMap a, [(Key, NEIntMap a)])
forall (t :: * -> *) a b c.
Traversable t =>
(a -> b -> (a, c)) -> a -> t b -> (a, t c)
L.mapAccumL IntMap a -> (Key, a) -> (IntMap a, (Key, NEIntMap a))
forall a. IntMap a -> (Key, a) -> (IntMap a, (Key, NEIntMap a))
go IntMap a
m0
                                    ([(Key, a)] -> (IntMap a, [(Key, NEIntMap a)]))
-> (IntMap a -> [(Key, a)])
-> IntMap a
-> (IntMap a, [(Key, NEIntMap a)])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. IntMap a -> [(Key, a)]
forall a. IntMap a -> [(Key, a)]
M.toList
                                    (IntMap a -> NEIntMap (NEIntMap a))
-> IntMap a -> NEIntMap (NEIntMap a)
forall a b. (a -> b) -> a -> b
$ IntMap a
m0
      where
        go :: IntMap a -> (Key, a) -> (IntMap a, (Key, NEIntMap a))
go IntMap a
m (Key
k, a
v) = (IntMap a
m', (Key
k, Key -> a -> IntMap a -> NEIntMap a
forall a. Key -> a -> IntMap a -> NEIntMap a
NEIntMap Key
k a
v IntMap a
m'))
          where
            !m' :: IntMap a
m' = IntMap a -> IntMap a
forall a. IntMap a -> IntMap a
M.deleteMin IntMap a
m
    {-# INLINE duplicate #-}
valid :: NEIntMap a -> Bool
valid :: NEIntMap a -> Bool
valid (NEIntMap Key
k a
_ IntMap a
m) = (((Key, a), IntMap a) -> Bool)
-> Maybe ((Key, a), IntMap a) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all ((Key
k Key -> Key -> Bool
forall a. Ord a => a -> a -> Bool
<) (Key -> Bool)
-> (((Key, a), IntMap a) -> Key) -> ((Key, a), IntMap a) -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Key, a) -> Key
forall a b. (a, b) -> a
fst ((Key, a) -> Key)
-> (((Key, a), IntMap a) -> (Key, a))
-> ((Key, a), IntMap a)
-> Key
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Key, a), IntMap a) -> (Key, a)
forall a b. (a, b) -> a
fst) (IntMap a -> Maybe ((Key, a), IntMap a)
forall a. IntMap a -> Maybe ((Key, a), IntMap a)
M.minViewWithKey IntMap a
m)
insertMinMap :: Key -> a -> IntMap a -> IntMap a
insertMinMap :: Key -> a -> IntMap a -> IntMap a
insertMinMap = Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
M.insert
{-# INLINABLE insertMinMap #-}
insertMaxMap :: Key -> a -> IntMap a -> IntMap a
insertMaxMap :: Key -> a -> IntMap a -> IntMap a
insertMaxMap = Key -> a -> IntMap a -> IntMap a
forall a. Key -> a -> IntMap a -> IntMap a
M.insert
{-# INLINABLE insertMaxMap #-}
traverseMapWithKey :: Applicative t => (Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseMapWithKey :: (Key -> a -> t b) -> IntMap a -> t (IntMap b)
traverseMapWithKey Key -> a -> t b
f = IntMap a -> t (IntMap b)
go
  where
    go :: IntMap a -> t (IntMap b)
go IntMap a
Nil = IntMap b -> t (IntMap b)
forall (f :: * -> *) a. Applicative f => a -> f a
pure IntMap b
forall a. IntMap a
Nil
    go (Tip Key
k a
v) = Key -> b -> IntMap b
forall a. Key -> a -> IntMap a
Tip Key
k (b -> IntMap b) -> t b -> t (IntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Key -> a -> t b
f Key
k a
v
    go (Bin Key
p Key
m IntMap a
l IntMap a
r) = (IntMap b -> IntMap b -> IntMap b)
-> t (IntMap b) -> t (IntMap b) -> t (IntMap b)
forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 ((IntMap b -> IntMap b -> IntMap b)
-> IntMap b -> IntMap b -> IntMap b
forall a b c. (a -> b -> c) -> b -> a -> c
flip (Key -> Key -> IntMap b -> IntMap b -> IntMap b
forall a. Key -> Key -> IntMap a -> IntMap a -> IntMap a
Bin Key
p Key
m)) (IntMap a -> t (IntMap b)
go IntMap a
r) (IntMap a -> t (IntMap b)
go IntMap a
l)
{-# INLINE traverseMapWithKey #-}
lookupMinMap :: IntMap a -> Maybe (Key, a)
#if MIN_VERSION_containers(0,5,11)
lookupMinMap :: IntMap a -> Maybe (Key, a)
lookupMinMap = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
M.lookupMin
#else
lookupMinMap = fmap fst . M.minViewWithKey
#endif
{-# INLINE lookupMinMap #-}
lookupMaxMap :: IntMap a -> Maybe (Key, a)
#if MIN_VERSION_containers(0,5,11)
lookupMaxMap :: IntMap a -> Maybe (Key, a)
lookupMaxMap = IntMap a -> Maybe (Key, a)
forall a. IntMap a -> Maybe (Key, a)
M.lookupMax
#else
lookupMaxMap = fmap fst . M.maxViewWithKey
#endif
{-# INLINE lookupMaxMap #-}