{-# LANGUAGE CPP #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE StandaloneDeriving #-}
module Data.IntMap.Monoidal
( MonoidalIntMap(..)
, singleton
, size
, member
, notMember
, findWithDefault
, assocs
, elems
, keys
, (!)
, (\\)
, adjust
, adjustWithKey
, alter
, delete
, deleteFindMax
, deleteFindMin
, deleteMax
, deleteMin
, difference
, differenceWith
, differenceWithKey
, empty
, filter
, filterWithKey
, findMax
, findMin
, foldMapWithKey
, foldl
, foldl'
, foldlWithKey
, foldlWithKey'
, foldr
, foldr'
, foldrWithKey
, foldrWithKey'
, fromAscList
, fromAscListWith
, fromAscListWithKey
, fromDistinctAscList
, fromDistinctList
, fromList
, fromListWith
, fromListWithKey
, fromSet
, insert
, insertLookupWithKey
, insertWith
, insertWithKey
, intersectionWith
, intersectionWithKey
, isProperSubmapOf
, isProperSubmapOfBy
, isSubmapOf
, isSubmapOfBy
, keysSet
, lookup
, lookupGE
, lookupGT
, lookupLE
, lookupLT
, map
, mapAccum
, mapAccumRWithKey
, mapAccumWithKey
, mapEither
, mapEitherWithKey
, mapKeys
, mapKeysMonotonic
, mapKeysWith
, mapMaybe
, mapMaybeWithKey
, mapWithKey
, maxView
, maxViewWithKey
, mergeWithKey
, minView
, minViewWithKey
, null
, partition
, partitionWithKey
, split
, splitLookup
, splitRoot
, toAscList
, toDescList
, toList
, traverseWithKey
, unionWith
, unionWithKey
, unionsWith
, update
, updateLookupWithKey
, updateMax
, updateMaxWithKey
, updateMin
, updateMinWithKey
, updateWithKey
) where
import Prelude hiding (null, lookup, map, foldl, foldr, filter)
import Data.Coerce (coerce)
import Data.IntSet (IntSet)
import Data.Semigroup
import Data.Foldable (Foldable)
import Data.Traversable (Traversable)
import Control.Applicative (Applicative, pure)
import Data.Data (Data)
import Data.Typeable (Typeable)
#if MIN_VERSION_base(4,7,0)
import qualified GHC.Exts as IsList
#endif
import Control.DeepSeq
import qualified Data.IntMap as M
import Control.Lens
import Control.Newtype
import Data.Aeson(FromJSON, ToJSON, FromJSON1, ToJSON1)
import Data.Functor.Classes
import Data.Align
#ifdef MIN_VERSION_semialign
import Data.Semialign (Unalign)
#if MIN_VERSION_semialign(1,1,0)
import Data.Zip (Zip)
#endif
#endif
import qualified Witherable
newtype MonoidalIntMap a = MonoidalIntMap { MonoidalIntMap a -> IntMap a
getMonoidalIntMap :: M.IntMap a }
deriving (Int -> MonoidalIntMap a -> ShowS
[MonoidalIntMap a] -> ShowS
MonoidalIntMap a -> String
(Int -> MonoidalIntMap a -> ShowS)
-> (MonoidalIntMap a -> String)
-> ([MonoidalIntMap a] -> ShowS)
-> Show (MonoidalIntMap a)
forall a. Show a => Int -> MonoidalIntMap a -> ShowS
forall a. Show a => [MonoidalIntMap a] -> ShowS
forall a. Show a => MonoidalIntMap a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [MonoidalIntMap a] -> ShowS
$cshowList :: forall a. Show a => [MonoidalIntMap a] -> ShowS
show :: MonoidalIntMap a -> String
$cshow :: forall a. Show a => MonoidalIntMap a -> String
showsPrec :: Int -> MonoidalIntMap a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> MonoidalIntMap a -> ShowS
Show, ReadPrec [MonoidalIntMap a]
ReadPrec (MonoidalIntMap a)
Int -> ReadS (MonoidalIntMap a)
ReadS [MonoidalIntMap a]
(Int -> ReadS (MonoidalIntMap a))
-> ReadS [MonoidalIntMap a]
-> ReadPrec (MonoidalIntMap a)
-> ReadPrec [MonoidalIntMap a]
-> Read (MonoidalIntMap a)
forall a. Read a => ReadPrec [MonoidalIntMap a]
forall a. Read a => ReadPrec (MonoidalIntMap a)
forall a. Read a => Int -> ReadS (MonoidalIntMap a)
forall a. Read a => ReadS [MonoidalIntMap a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [MonoidalIntMap a]
$creadListPrec :: forall a. Read a => ReadPrec [MonoidalIntMap a]
readPrec :: ReadPrec (MonoidalIntMap a)
$creadPrec :: forall a. Read a => ReadPrec (MonoidalIntMap a)
readList :: ReadS [MonoidalIntMap a]
$creadList :: forall a. Read a => ReadS [MonoidalIntMap a]
readsPrec :: Int -> ReadS (MonoidalIntMap a)
$creadsPrec :: forall a. Read a => Int -> ReadS (MonoidalIntMap a)
Read, a -> MonoidalIntMap b -> MonoidalIntMap a
(a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
(forall a b. (a -> b) -> MonoidalIntMap a -> MonoidalIntMap b)
-> (forall a b. a -> MonoidalIntMap b -> MonoidalIntMap a)
-> Functor MonoidalIntMap
forall a b. a -> MonoidalIntMap b -> MonoidalIntMap a
forall a b. (a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> MonoidalIntMap b -> MonoidalIntMap a
$c<$ :: forall a b. a -> MonoidalIntMap b -> MonoidalIntMap a
fmap :: (a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
$cfmap :: forall a b. (a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
Functor, MonoidalIntMap a -> MonoidalIntMap a -> Bool
(MonoidalIntMap a -> MonoidalIntMap a -> Bool)
-> (MonoidalIntMap a -> MonoidalIntMap a -> Bool)
-> Eq (MonoidalIntMap a)
forall a. Eq a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
$c/= :: forall a. Eq a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
== :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
$c== :: forall a. Eq a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
Eq, Eq (MonoidalIntMap a)
Eq (MonoidalIntMap a)
-> (MonoidalIntMap a -> MonoidalIntMap a -> Ordering)
-> (MonoidalIntMap a -> MonoidalIntMap a -> Bool)
-> (MonoidalIntMap a -> MonoidalIntMap a -> Bool)
-> (MonoidalIntMap a -> MonoidalIntMap a -> Bool)
-> (MonoidalIntMap a -> MonoidalIntMap a -> Bool)
-> (MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a)
-> (MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a)
-> Ord (MonoidalIntMap a)
MonoidalIntMap a -> MonoidalIntMap a -> Bool
MonoidalIntMap a -> MonoidalIntMap a -> Ordering
MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
forall a. Ord a => Eq (MonoidalIntMap a)
forall a. Ord a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
forall a. Ord a => MonoidalIntMap a -> MonoidalIntMap a -> Ordering
forall a.
Ord a =>
MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
min :: MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
$cmin :: forall a.
Ord a =>
MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
max :: MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
$cmax :: forall a.
Ord a =>
MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
>= :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
$c>= :: forall a. Ord a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
> :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
$c> :: forall a. Ord a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
<= :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
$c<= :: forall a. Ord a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
< :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
$c< :: forall a. Ord a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
compare :: MonoidalIntMap a -> MonoidalIntMap a -> Ordering
$ccompare :: forall a. Ord a => MonoidalIntMap a -> MonoidalIntMap a -> Ordering
$cp1Ord :: forall a. Ord a => Eq (MonoidalIntMap a)
Ord, MonoidalIntMap a -> ()
(MonoidalIntMap a -> ()) -> NFData (MonoidalIntMap a)
forall a. NFData a => MonoidalIntMap a -> ()
forall a. (a -> ()) -> NFData a
rnf :: MonoidalIntMap a -> ()
$crnf :: forall a. NFData a => MonoidalIntMap a -> ()
NFData,
a -> MonoidalIntMap a -> Bool
MonoidalIntMap m -> m
MonoidalIntMap a -> [a]
MonoidalIntMap a -> Bool
MonoidalIntMap a -> Int
MonoidalIntMap a -> a
MonoidalIntMap a -> a
MonoidalIntMap a -> a
MonoidalIntMap a -> a
(a -> m) -> MonoidalIntMap a -> m
(a -> m) -> MonoidalIntMap a -> m
(a -> b -> b) -> b -> MonoidalIntMap a -> b
(a -> b -> b) -> b -> MonoidalIntMap a -> b
(b -> a -> b) -> b -> MonoidalIntMap a -> b
(b -> a -> b) -> b -> MonoidalIntMap a -> b
(a -> a -> a) -> MonoidalIntMap a -> a
(a -> a -> a) -> MonoidalIntMap a -> a
(forall m. Monoid m => MonoidalIntMap m -> m)
-> (forall m a. Monoid m => (a -> m) -> MonoidalIntMap a -> m)
-> (forall m a. Monoid m => (a -> m) -> MonoidalIntMap a -> m)
-> (forall a b. (a -> b -> b) -> b -> MonoidalIntMap a -> b)
-> (forall a b. (a -> b -> b) -> b -> MonoidalIntMap a -> b)
-> (forall b a. (b -> a -> b) -> b -> MonoidalIntMap a -> b)
-> (forall b a. (b -> a -> b) -> b -> MonoidalIntMap a -> b)
-> (forall a. (a -> a -> a) -> MonoidalIntMap a -> a)
-> (forall a. (a -> a -> a) -> MonoidalIntMap a -> a)
-> (forall a. MonoidalIntMap a -> [a])
-> (forall a. MonoidalIntMap a -> Bool)
-> (forall a. MonoidalIntMap a -> Int)
-> (forall a. Eq a => a -> MonoidalIntMap a -> Bool)
-> (forall a. Ord a => MonoidalIntMap a -> a)
-> (forall a. Ord a => MonoidalIntMap a -> a)
-> (forall a. Num a => MonoidalIntMap a -> a)
-> (forall a. Num a => MonoidalIntMap a -> a)
-> Foldable MonoidalIntMap
forall a. Eq a => a -> MonoidalIntMap a -> Bool
forall a. Num a => MonoidalIntMap a -> a
forall a. Ord a => MonoidalIntMap a -> a
forall m. Monoid m => MonoidalIntMap m -> m
forall a. MonoidalIntMap a -> Bool
forall a. MonoidalIntMap a -> Int
forall a. MonoidalIntMap a -> [a]
forall a. (a -> a -> a) -> MonoidalIntMap a -> a
forall m a. Monoid m => (a -> m) -> MonoidalIntMap a -> m
forall b a. (b -> a -> b) -> b -> MonoidalIntMap a -> b
forall a b. (a -> b -> b) -> b -> MonoidalIntMap a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: MonoidalIntMap a -> a
$cproduct :: forall a. Num a => MonoidalIntMap a -> a
sum :: MonoidalIntMap a -> a
$csum :: forall a. Num a => MonoidalIntMap a -> a
minimum :: MonoidalIntMap a -> a
$cminimum :: forall a. Ord a => MonoidalIntMap a -> a
maximum :: MonoidalIntMap a -> a
$cmaximum :: forall a. Ord a => MonoidalIntMap a -> a
elem :: a -> MonoidalIntMap a -> Bool
$celem :: forall a. Eq a => a -> MonoidalIntMap a -> Bool
length :: MonoidalIntMap a -> Int
$clength :: forall a. MonoidalIntMap a -> Int
null :: MonoidalIntMap a -> Bool
$cnull :: forall a. MonoidalIntMap a -> Bool
toList :: MonoidalIntMap a -> [a]
$ctoList :: forall a. MonoidalIntMap a -> [a]
foldl1 :: (a -> a -> a) -> MonoidalIntMap a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> MonoidalIntMap a -> a
foldr1 :: (a -> a -> a) -> MonoidalIntMap a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> MonoidalIntMap a -> a
foldl' :: (b -> a -> b) -> b -> MonoidalIntMap a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> MonoidalIntMap a -> b
foldl :: (b -> a -> b) -> b -> MonoidalIntMap a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> MonoidalIntMap a -> b
foldr' :: (a -> b -> b) -> b -> MonoidalIntMap a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> MonoidalIntMap a -> b
foldr :: (a -> b -> b) -> b -> MonoidalIntMap a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> MonoidalIntMap a -> b
foldMap' :: (a -> m) -> MonoidalIntMap a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> MonoidalIntMap a -> m
foldMap :: (a -> m) -> MonoidalIntMap a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> MonoidalIntMap a -> m
fold :: MonoidalIntMap m -> m
$cfold :: forall m. Monoid m => MonoidalIntMap m -> m
Foldable, Functor MonoidalIntMap
Foldable MonoidalIntMap
Functor MonoidalIntMap
-> Foldable MonoidalIntMap
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MonoidalIntMap a -> f (MonoidalIntMap b))
-> (forall (f :: * -> *) a.
Applicative f =>
MonoidalIntMap (f a) -> f (MonoidalIntMap a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MonoidalIntMap a -> m (MonoidalIntMap b))
-> (forall (m :: * -> *) a.
Monad m =>
MonoidalIntMap (m a) -> m (MonoidalIntMap a))
-> Traversable MonoidalIntMap
(a -> f b) -> MonoidalIntMap a -> f (MonoidalIntMap b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a.
Monad m =>
MonoidalIntMap (m a) -> m (MonoidalIntMap a)
forall (f :: * -> *) a.
Applicative f =>
MonoidalIntMap (f a) -> f (MonoidalIntMap a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MonoidalIntMap a -> m (MonoidalIntMap b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MonoidalIntMap a -> f (MonoidalIntMap b)
sequence :: MonoidalIntMap (m a) -> m (MonoidalIntMap a)
$csequence :: forall (m :: * -> *) a.
Monad m =>
MonoidalIntMap (m a) -> m (MonoidalIntMap a)
mapM :: (a -> m b) -> MonoidalIntMap a -> m (MonoidalIntMap b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> MonoidalIntMap a -> m (MonoidalIntMap b)
sequenceA :: MonoidalIntMap (f a) -> f (MonoidalIntMap a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
MonoidalIntMap (f a) -> f (MonoidalIntMap a)
traverse :: (a -> f b) -> MonoidalIntMap a -> f (MonoidalIntMap b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> MonoidalIntMap a -> f (MonoidalIntMap b)
$cp2Traversable :: Foldable MonoidalIntMap
$cp1Traversable :: Functor MonoidalIntMap
Traversable,
Value -> Parser [MonoidalIntMap a]
Value -> Parser (MonoidalIntMap a)
(Value -> Parser (MonoidalIntMap a))
-> (Value -> Parser [MonoidalIntMap a])
-> FromJSON (MonoidalIntMap a)
forall a. FromJSON a => Value -> Parser [MonoidalIntMap a]
forall a. FromJSON a => Value -> Parser (MonoidalIntMap a)
forall a.
(Value -> Parser a) -> (Value -> Parser [a]) -> FromJSON a
parseJSONList :: Value -> Parser [MonoidalIntMap a]
$cparseJSONList :: forall a. FromJSON a => Value -> Parser [MonoidalIntMap a]
parseJSON :: Value -> Parser (MonoidalIntMap a)
$cparseJSON :: forall a. FromJSON a => Value -> Parser (MonoidalIntMap a)
FromJSON, [MonoidalIntMap a] -> Encoding
[MonoidalIntMap a] -> Value
MonoidalIntMap a -> Encoding
MonoidalIntMap a -> Value
(MonoidalIntMap a -> Value)
-> (MonoidalIntMap a -> Encoding)
-> ([MonoidalIntMap a] -> Value)
-> ([MonoidalIntMap a] -> Encoding)
-> ToJSON (MonoidalIntMap a)
forall a. ToJSON a => [MonoidalIntMap a] -> Encoding
forall a. ToJSON a => [MonoidalIntMap a] -> Value
forall a. ToJSON a => MonoidalIntMap a -> Encoding
forall a. ToJSON a => MonoidalIntMap a -> Value
forall a.
(a -> Value)
-> (a -> Encoding)
-> ([a] -> Value)
-> ([a] -> Encoding)
-> ToJSON a
toEncodingList :: [MonoidalIntMap a] -> Encoding
$ctoEncodingList :: forall a. ToJSON a => [MonoidalIntMap a] -> Encoding
toJSONList :: [MonoidalIntMap a] -> Value
$ctoJSONList :: forall a. ToJSON a => [MonoidalIntMap a] -> Value
toEncoding :: MonoidalIntMap a -> Encoding
$ctoEncoding :: forall a. ToJSON a => MonoidalIntMap a -> Encoding
toJSON :: MonoidalIntMap a -> Value
$ctoJSON :: forall a. ToJSON a => MonoidalIntMap a -> Value
ToJSON, (Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser (MonoidalIntMap a)
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser [MonoidalIntMap a]
(forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser (MonoidalIntMap a))
-> (forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser [MonoidalIntMap a])
-> FromJSON1 MonoidalIntMap
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser [MonoidalIntMap a]
forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser (MonoidalIntMap a)
forall (f :: * -> *).
(forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser (f a))
-> (forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser [f a])
-> FromJSON1 f
liftParseJSONList :: (Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser [MonoidalIntMap a]
$cliftParseJSONList :: forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser [MonoidalIntMap a]
liftParseJSON :: (Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser (MonoidalIntMap a)
$cliftParseJSON :: forall a.
(Value -> Parser a)
-> (Value -> Parser [a]) -> Value -> Parser (MonoidalIntMap a)
FromJSON1, (a -> Value) -> ([a] -> Value) -> MonoidalIntMap a -> Value
(a -> Value) -> ([a] -> Value) -> [MonoidalIntMap a] -> Value
(a -> Encoding)
-> ([a] -> Encoding) -> MonoidalIntMap a -> Encoding
(a -> Encoding)
-> ([a] -> Encoding) -> [MonoidalIntMap a] -> Encoding
(forall a.
(a -> Value) -> ([a] -> Value) -> MonoidalIntMap a -> Value)
-> (forall a.
(a -> Value) -> ([a] -> Value) -> [MonoidalIntMap a] -> Value)
-> (forall a.
(a -> Encoding)
-> ([a] -> Encoding) -> MonoidalIntMap a -> Encoding)
-> (forall a.
(a -> Encoding)
-> ([a] -> Encoding) -> [MonoidalIntMap a] -> Encoding)
-> ToJSON1 MonoidalIntMap
forall a.
(a -> Encoding)
-> ([a] -> Encoding) -> [MonoidalIntMap a] -> Encoding
forall a.
(a -> Encoding)
-> ([a] -> Encoding) -> MonoidalIntMap a -> Encoding
forall a.
(a -> Value) -> ([a] -> Value) -> [MonoidalIntMap a] -> Value
forall a.
(a -> Value) -> ([a] -> Value) -> MonoidalIntMap a -> Value
forall (f :: * -> *).
(forall a. (a -> Value) -> ([a] -> Value) -> f a -> Value)
-> (forall a. (a -> Value) -> ([a] -> Value) -> [f a] -> Value)
-> (forall a.
(a -> Encoding) -> ([a] -> Encoding) -> f a -> Encoding)
-> (forall a.
(a -> Encoding) -> ([a] -> Encoding) -> [f a] -> Encoding)
-> ToJSON1 f
liftToEncodingList :: (a -> Encoding)
-> ([a] -> Encoding) -> [MonoidalIntMap a] -> Encoding
$cliftToEncodingList :: forall a.
(a -> Encoding)
-> ([a] -> Encoding) -> [MonoidalIntMap a] -> Encoding
liftToEncoding :: (a -> Encoding)
-> ([a] -> Encoding) -> MonoidalIntMap a -> Encoding
$cliftToEncoding :: forall a.
(a -> Encoding)
-> ([a] -> Encoding) -> MonoidalIntMap a -> Encoding
liftToJSONList :: (a -> Value) -> ([a] -> Value) -> [MonoidalIntMap a] -> Value
$cliftToJSONList :: forall a.
(a -> Value) -> ([a] -> Value) -> [MonoidalIntMap a] -> Value
liftToJSON :: (a -> Value) -> ([a] -> Value) -> MonoidalIntMap a -> Value
$cliftToJSON :: forall a.
(a -> Value) -> ([a] -> Value) -> MonoidalIntMap a -> Value
ToJSON1,
Typeable (MonoidalIntMap a)
DataType
Constr
Typeable (MonoidalIntMap a)
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g)
-> MonoidalIntMap a
-> c (MonoidalIntMap a))
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MonoidalIntMap a))
-> (MonoidalIntMap a -> Constr)
-> (MonoidalIntMap a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (MonoidalIntMap a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MonoidalIntMap a)))
-> ((forall b. Data b => b -> b)
-> MonoidalIntMap a -> MonoidalIntMap a)
-> (forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r)
-> (forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r)
-> (forall u.
(forall d. Data d => d -> u) -> MonoidalIntMap a -> [u])
-> (forall u.
Int -> (forall d. Data d => d -> u) -> MonoidalIntMap a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a))
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a))
-> Data (MonoidalIntMap a)
MonoidalIntMap a -> DataType
MonoidalIntMap a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (MonoidalIntMap a))
(forall b. Data b => b -> b)
-> MonoidalIntMap a -> MonoidalIntMap a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MonoidalIntMap a -> c (MonoidalIntMap a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MonoidalIntMap a)
forall a. Data a => Typeable (MonoidalIntMap a)
forall a. Data a => MonoidalIntMap a -> DataType
forall a. Data a => MonoidalIntMap a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b)
-> MonoidalIntMap a -> MonoidalIntMap a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> MonoidalIntMap a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> MonoidalIntMap a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MonoidalIntMap a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MonoidalIntMap a -> c (MonoidalIntMap a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (MonoidalIntMap a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MonoidalIntMap a))
forall a.
Typeable a
-> (forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u.
Int -> (forall d. Data d => d -> u) -> MonoidalIntMap a -> u
forall u. (forall d. Data d => d -> u) -> MonoidalIntMap a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MonoidalIntMap a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MonoidalIntMap a -> c (MonoidalIntMap a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (MonoidalIntMap a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MonoidalIntMap a))
$cMonoidalIntMap :: Constr
$tMonoidalIntMap :: DataType
gmapMo :: (forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
gmapMp :: (forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
gmapM :: (forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d)
-> MonoidalIntMap a -> m (MonoidalIntMap a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> MonoidalIntMap a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> MonoidalIntMap a -> u
gmapQ :: (forall d. Data d => d -> u) -> MonoidalIntMap a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> MonoidalIntMap a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> MonoidalIntMap a -> r
gmapT :: (forall b. Data b => b -> b)
-> MonoidalIntMap a -> MonoidalIntMap a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b)
-> MonoidalIntMap a -> MonoidalIntMap a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MonoidalIntMap a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (MonoidalIntMap a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (MonoidalIntMap a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (MonoidalIntMap a))
dataTypeOf :: MonoidalIntMap a -> DataType
$cdataTypeOf :: forall a. Data a => MonoidalIntMap a -> DataType
toConstr :: MonoidalIntMap a -> Constr
$ctoConstr :: forall a. Data a => MonoidalIntMap a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MonoidalIntMap a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (MonoidalIntMap a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MonoidalIntMap a -> c (MonoidalIntMap a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> MonoidalIntMap a -> c (MonoidalIntMap a)
$cp1Data :: forall a. Data a => Typeable (MonoidalIntMap a)
Data, Typeable, Semialign MonoidalIntMap
MonoidalIntMap a
Semialign MonoidalIntMap
-> (forall a. MonoidalIntMap a) -> Align MonoidalIntMap
forall a. MonoidalIntMap a
forall (f :: * -> *). Semialign f -> (forall a. f a) -> Align f
nil :: MonoidalIntMap a
$cnil :: forall a. MonoidalIntMap a
$cp1Align :: Semialign MonoidalIntMap
Align
#if MIN_VERSION_these(0,8,0)
, Functor MonoidalIntMap
Functor MonoidalIntMap
-> (forall a b.
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (These a b))
-> (forall a b c.
(These a b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c)
-> Semialign MonoidalIntMap
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (These a b)
(These a b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
forall a b.
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (These a b)
forall a b c.
(These a b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
forall (f :: * -> *).
Functor f
-> (forall a b. f a -> f b -> f (These a b))
-> (forall a b c. (These a b -> c) -> f a -> f b -> f c)
-> Semialign f
alignWith :: (These a b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
$calignWith :: forall a b c.
(These a b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
align :: MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (These a b)
$calign :: forall a b.
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (These a b)
$cp1Semialign :: Functor MonoidalIntMap
Semialign
#endif
#ifdef MIN_VERSION_semialign
, Semialign MonoidalIntMap
Semialign MonoidalIntMap
-> (forall a b.
MonoidalIntMap (These a b) -> (MonoidalIntMap a, MonoidalIntMap b))
-> (forall c a b.
(c -> These a b)
-> MonoidalIntMap c -> (MonoidalIntMap a, MonoidalIntMap b))
-> Unalign MonoidalIntMap
MonoidalIntMap (These a b) -> (MonoidalIntMap a, MonoidalIntMap b)
(c -> These a b)
-> MonoidalIntMap c -> (MonoidalIntMap a, MonoidalIntMap b)
forall a b.
MonoidalIntMap (These a b) -> (MonoidalIntMap a, MonoidalIntMap b)
forall c a b.
(c -> These a b)
-> MonoidalIntMap c -> (MonoidalIntMap a, MonoidalIntMap b)
forall (f :: * -> *).
Semialign f
-> (forall a b. f (These a b) -> (f a, f b))
-> (forall c a b. (c -> These a b) -> f c -> (f a, f b))
-> Unalign f
unalignWith :: (c -> These a b)
-> MonoidalIntMap c -> (MonoidalIntMap a, MonoidalIntMap b)
$cunalignWith :: forall c a b.
(c -> These a b)
-> MonoidalIntMap c -> (MonoidalIntMap a, MonoidalIntMap b)
unalign :: MonoidalIntMap (These a b) -> (MonoidalIntMap a, MonoidalIntMap b)
$cunalign :: forall a b.
MonoidalIntMap (These a b) -> (MonoidalIntMap a, MonoidalIntMap b)
$cp1Unalign :: Semialign MonoidalIntMap
Unalign
#if MIN_VERSION_semialign(1,1,0)
, Semialign MonoidalIntMap
Semialign MonoidalIntMap
-> (forall a b.
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (a, b))
-> (forall a b c.
(a -> b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c)
-> Zip MonoidalIntMap
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (a, b)
(a -> b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
forall a b.
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (a, b)
forall a b c.
(a -> b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
forall (f :: * -> *).
Semialign f
-> (forall a b. f a -> f b -> f (a, b))
-> (forall a b c. (a -> b -> c) -> f a -> f b -> f c)
-> Zip f
zipWith :: (a -> b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
$czipWith :: forall a b c.
(a -> b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
zip :: MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (a, b)
$czip :: forall a b.
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap (a, b)
$cp1Zip :: Semialign MonoidalIntMap
Zip
#endif
#endif
, Functor MonoidalIntMap
Functor MonoidalIntMap
-> (forall a b.
(a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b)
-> (forall a. MonoidalIntMap (Maybe a) -> MonoidalIntMap a)
-> (forall a. (a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a)
-> Filterable MonoidalIntMap
MonoidalIntMap (Maybe a) -> MonoidalIntMap a
(a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
(a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
forall a. MonoidalIntMap (Maybe a) -> MonoidalIntMap a
forall a. (a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
forall a b. (a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
forall (f :: * -> *).
Functor f
-> (forall a b. (a -> Maybe b) -> f a -> f b)
-> (forall a. f (Maybe a) -> f a)
-> (forall a. (a -> Bool) -> f a -> f a)
-> Filterable f
filter :: (a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
$cfilter :: forall a. (a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
catMaybes :: MonoidalIntMap (Maybe a) -> MonoidalIntMap a
$ccatMaybes :: forall a. MonoidalIntMap (Maybe a) -> MonoidalIntMap a
mapMaybe :: (a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
$cmapMaybe :: forall a b. (a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
$cp1Filterable :: Functor MonoidalIntMap
Witherable.Filterable
)
deriving instance Eq1 MonoidalIntMap
deriving instance Ord1 MonoidalIntMap
deriving instance Show1 MonoidalIntMap
type instance Index (MonoidalIntMap a) = Int
type instance IxValue (MonoidalIntMap a) = a
instance Ixed (MonoidalIntMap a) where
ix :: Index (MonoidalIntMap a)
-> Traversal' (MonoidalIntMap a) (IxValue (MonoidalIntMap a))
ix Index (MonoidalIntMap a)
k IxValue (MonoidalIntMap a) -> f (IxValue (MonoidalIntMap a))
f (MonoidalIntMap IntMap a
m) = case Int -> IntMap a -> Maybe a
forall a. Int -> IntMap a -> Maybe a
M.lookup Int
Index (MonoidalIntMap a)
k IntMap a
m of
Just a
v -> IxValue (MonoidalIntMap a) -> f (IxValue (MonoidalIntMap a))
f a
IxValue (MonoidalIntMap a)
v f a -> (a -> MonoidalIntMap a) -> f (MonoidalIntMap a)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \a
v' -> IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (Int -> a -> IntMap a -> IntMap a
forall a. Int -> a -> IntMap a -> IntMap a
M.insert Int
Index (MonoidalIntMap a)
k a
v' IntMap a
m)
Maybe a
Nothing -> MonoidalIntMap a -> f (MonoidalIntMap a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure (IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap IntMap a
m)
{-# INLINE ix #-}
instance At (MonoidalIntMap a) where
at :: Index (MonoidalIntMap a)
-> Lens' (MonoidalIntMap a) (Maybe (IxValue (MonoidalIntMap a)))
at Index (MonoidalIntMap a)
k Maybe (IxValue (MonoidalIntMap a))
-> f (Maybe (IxValue (MonoidalIntMap a)))
f (MonoidalIntMap IntMap a
m) = Maybe (IxValue (MonoidalIntMap a))
-> f (Maybe (IxValue (MonoidalIntMap a)))
f Maybe a
Maybe (IxValue (MonoidalIntMap a))
mv f (Maybe a)
-> (Maybe a -> MonoidalIntMap a) -> f (MonoidalIntMap a)
forall (f :: * -> *) a b. Functor f => f a -> (a -> b) -> f b
<&> \Maybe a
r -> case Maybe a
r of
Maybe a
Nothing -> MonoidalIntMap a
-> (a -> MonoidalIntMap a) -> Maybe a -> MonoidalIntMap a
forall b a. b -> (a -> b) -> Maybe a -> b
maybe (IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap IntMap a
m) (MonoidalIntMap a -> a -> MonoidalIntMap a
forall a b. a -> b -> a
const (IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (IntMap a -> MonoidalIntMap a) -> IntMap a -> MonoidalIntMap a
forall a b. (a -> b) -> a -> b
$ Int -> IntMap a -> IntMap a
forall a. Int -> IntMap a -> IntMap a
M.delete Int
Index (MonoidalIntMap a)
k IntMap a
m)) Maybe a
mv
Just a
v' -> IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (IntMap a -> MonoidalIntMap a) -> IntMap a -> MonoidalIntMap a
forall a b. (a -> b) -> a -> b
$ Int -> a -> IntMap a -> IntMap a
forall a. Int -> a -> IntMap a -> IntMap a
M.insert Int
Index (MonoidalIntMap a)
k a
v' IntMap a
m
where mv :: Maybe a
mv = Int -> IntMap a -> Maybe a
forall a. Int -> IntMap a -> Maybe a
M.lookup Int
Index (MonoidalIntMap a)
k IntMap a
m
{-# INLINE at #-}
instance Each (MonoidalIntMap a) (MonoidalIntMap b) a b
instance FunctorWithIndex Int MonoidalIntMap
instance FoldableWithIndex Int MonoidalIntMap
instance TraversableWithIndex Int MonoidalIntMap where
itraverse :: (Int -> a -> f b) -> MonoidalIntMap a -> f (MonoidalIntMap b)
itraverse Int -> a -> f b
f (MonoidalIntMap IntMap a
m) = (IntMap b -> MonoidalIntMap b)
-> f (IntMap b) -> f (MonoidalIntMap b)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IntMap b -> MonoidalIntMap b
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (f (IntMap b) -> f (MonoidalIntMap b))
-> f (IntMap b) -> f (MonoidalIntMap b)
forall a b. (a -> b) -> a -> b
$ (Int -> a -> f b) -> IntMap a -> f (IntMap b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse Int -> a -> f b
f IntMap a
m
{-# INLINE itraverse #-}
instance TraverseMin Int MonoidalIntMap where
traverseMin :: p v (f v) -> MonoidalIntMap v -> f (MonoidalIntMap v)
traverseMin p v (f v)
f (MonoidalIntMap IntMap v
m) = (IntMap v -> MonoidalIntMap v)
-> f (IntMap v) -> f (MonoidalIntMap v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IntMap v -> MonoidalIntMap v
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (f (IntMap v) -> f (MonoidalIntMap v))
-> f (IntMap v) -> f (MonoidalIntMap v)
forall a b. (a -> b) -> a -> b
$ p v (f v) -> IntMap v -> f (IntMap v)
forall k (m :: * -> *) v.
TraverseMin k m =>
IndexedTraversal' k (m v) v
traverseMin p v (f v)
f IntMap v
m
{-# INLINE traverseMin #-}
instance TraverseMax Int MonoidalIntMap where
traverseMax :: p v (f v) -> MonoidalIntMap v -> f (MonoidalIntMap v)
traverseMax p v (f v)
f (MonoidalIntMap IntMap v
m) = (IntMap v -> MonoidalIntMap v)
-> f (IntMap v) -> f (MonoidalIntMap v)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap IntMap v -> MonoidalIntMap v
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (f (IntMap v) -> f (MonoidalIntMap v))
-> f (IntMap v) -> f (MonoidalIntMap v)
forall a b. (a -> b) -> a -> b
$ p v (f v) -> IntMap v -> f (IntMap v)
forall k (m :: * -> *) v.
TraverseMax k m =>
IndexedTraversal' k (m v) v
traverseMax p v (f v)
f IntMap v
m
{-# INLINE traverseMax #-}
instance AsEmpty (MonoidalIntMap a) where
_Empty :: p () (f ()) -> p (MonoidalIntMap a) (f (MonoidalIntMap a))
_Empty = MonoidalIntMap a
-> (MonoidalIntMap a -> Bool) -> Prism' (MonoidalIntMap a) ()
forall a. a -> (a -> Bool) -> Prism' a ()
nearly (IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap IntMap a
forall a. IntMap a
M.empty) (IntMap a -> Bool
forall a. IntMap a -> Bool
M.null (IntMap a -> Bool)
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack)
{-# INLINE _Empty #-}
instance Wrapped (MonoidalIntMap a) where
type Unwrapped (MonoidalIntMap a) = M.IntMap a
_Wrapped' :: p (Unwrapped (MonoidalIntMap a)) (f (Unwrapped (MonoidalIntMap a)))
-> p (MonoidalIntMap a) (f (MonoidalIntMap a))
_Wrapped' = (MonoidalIntMap a -> IntMap a)
-> (IntMap a -> MonoidalIntMap a)
-> Iso (MonoidalIntMap a) (MonoidalIntMap a) (IntMap a) (IntMap a)
forall s a b t. (s -> a) -> (b -> t) -> Iso s t a b
iso MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack IntMap a -> MonoidalIntMap a
forall n o. Newtype n o => o -> n
pack
{-# INLINE _Wrapped' #-}
instance Semigroup a => Semigroup (MonoidalIntMap a) where
MonoidalIntMap IntMap a
a <> :: MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
<> MonoidalIntMap IntMap a
b = IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (IntMap a -> MonoidalIntMap a) -> IntMap a -> MonoidalIntMap a
forall a b. (a -> b) -> a -> b
$ (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWith a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>) IntMap a
a IntMap a
b
{-# INLINE (<>) #-}
instance Semigroup a => Monoid (MonoidalIntMap a) where
mempty :: MonoidalIntMap a
mempty = IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap IntMap a
forall a. Monoid a => a
mempty
{-# INLINE mempty #-}
#if !(MIN_VERSION_base(4,11,0))
mappend (MonoidalIntMap a) (MonoidalIntMap b) = MonoidalIntMap $ M.unionWith (<>) a b
{-# INLINE mappend #-}
#endif
instance Newtype (MonoidalIntMap a) (M.IntMap a) where
pack :: IntMap a -> MonoidalIntMap a
pack = IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap
{-# INLINE pack #-}
unpack :: MonoidalIntMap a -> IntMap a
unpack (MonoidalIntMap IntMap a
a) = IntMap a
a
{-# INLINE unpack #-}
#if MIN_VERSION_base(4,7,0)
instance Semigroup a => IsList.IsList (MonoidalIntMap a) where
type Item (MonoidalIntMap a) = (Int, a)
fromList :: [Item (MonoidalIntMap a)] -> MonoidalIntMap a
fromList = IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (IntMap a -> MonoidalIntMap a)
-> ([(Int, a)] -> IntMap a) -> [(Int, a)] -> MonoidalIntMap a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (a -> a -> a) -> [(Int, a)] -> IntMap a
forall a. (a -> a -> a) -> [(Int, a)] -> IntMap a
M.fromListWith a -> a -> a
forall a. Semigroup a => a -> a -> a
(<>)
{-# INLINE fromList #-}
toList :: MonoidalIntMap a -> [Item (MonoidalIntMap a)]
toList = IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
M.toList (IntMap a -> [(Int, a)])
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> [(Int, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE toList #-}
#endif
instance Witherable.Witherable MonoidalIntMap
singleton :: Int -> a -> MonoidalIntMap a
singleton :: Int -> a -> MonoidalIntMap a
singleton Int
k a
a = IntMap a -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap (IntMap a -> MonoidalIntMap a) -> IntMap a -> MonoidalIntMap a
forall a b. (a -> b) -> a -> b
$ Int -> a -> IntMap a
forall a. Int -> a -> IntMap a
M.singleton Int
k a
a
{-# INLINE singleton #-}
size :: MonoidalIntMap a -> Int
size :: MonoidalIntMap a -> Int
size = IntMap a -> Int
forall a. IntMap a -> Int
M.size (IntMap a -> Int)
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> Int
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE size #-}
member :: Int -> MonoidalIntMap a -> Bool
member :: Int -> MonoidalIntMap a -> Bool
member Int
k = Int -> IntMap a -> Bool
forall a. Int -> IntMap a -> Bool
M.member Int
k (IntMap a -> Bool)
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE member #-}
notMember :: Int -> MonoidalIntMap a -> Bool
notMember :: Int -> MonoidalIntMap a -> Bool
notMember Int
k = Bool -> Bool
not (Bool -> Bool)
-> (MonoidalIntMap a -> Bool) -> MonoidalIntMap a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> IntMap a -> Bool
forall a. Int -> IntMap a -> Bool
M.member Int
k (IntMap a -> Bool)
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE notMember #-}
findWithDefault :: forall a. a -> Int -> MonoidalIntMap a -> a
findWithDefault :: a -> Int -> MonoidalIntMap a -> a
findWithDefault a
def Int
k = a -> Int -> IntMap a -> a
forall a. a -> Int -> IntMap a -> a
M.findWithDefault a
def Int
k (IntMap a -> a)
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> a
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE findWithDefault #-}
delete :: Int -> MonoidalIntMap a -> MonoidalIntMap a
delete :: Int -> MonoidalIntMap a -> MonoidalIntMap a
delete Int
k = (Unwrapped (MonoidalIntMap a) -> MonoidalIntMap a)
-> Iso' (MonoidalIntMap a) (Unwrapped (MonoidalIntMap a))
forall s. Wrapped s => (Unwrapped s -> s) -> Iso' s (Unwrapped s)
_Wrapping' Unwrapped (MonoidalIntMap a) -> MonoidalIntMap a
forall a. IntMap a -> MonoidalIntMap a
MonoidalIntMap ((IntMap a -> Identity (IntMap a))
-> MonoidalIntMap a -> Identity (MonoidalIntMap a))
-> (IntMap a -> IntMap a) -> MonoidalIntMap a -> MonoidalIntMap a
forall s t a b. ASetter s t a b -> (a -> b) -> s -> t
%~ Int -> IntMap a -> IntMap a
forall a. Int -> IntMap a -> IntMap a
M.delete Int
k
{-# INLINE delete #-}
assocs :: MonoidalIntMap a -> [(Int,a)]
assocs :: MonoidalIntMap a -> [(Int, a)]
assocs = IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
M.assocs (IntMap a -> [(Int, a)])
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> [(Int, a)]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE assocs #-}
elems :: MonoidalIntMap a -> [a]
elems :: MonoidalIntMap a -> [a]
elems = IntMap a -> [a]
forall a. IntMap a -> [a]
M.elems (IntMap a -> [a])
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE elems #-}
keys :: MonoidalIntMap a -> [Int]
keys :: MonoidalIntMap a -> [Int]
keys = IntMap a -> [Int]
forall a. IntMap a -> [Int]
M.keys (IntMap a -> [Int])
-> (MonoidalIntMap a -> IntMap a) -> MonoidalIntMap a -> [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. MonoidalIntMap a -> IntMap a
forall n o. Newtype n o => n -> o
unpack
{-# INLINE keys #-}
(!) :: forall a. MonoidalIntMap a -> Int -> a
(!) = (IntMap a -> Int -> a) -> MonoidalIntMap a -> Int -> a
coerce (IntMap a -> Int -> a
forall a. IntMap a -> Int -> a
(M.!) :: M.IntMap a -> Int -> a)
infixl 9 !
(\\) :: forall a b. MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
\\ :: MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
(\\) = (IntMap a -> IntMap b -> IntMap a)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
coerce (IntMap a -> IntMap b -> IntMap a
forall a b. IntMap a -> IntMap b -> IntMap a
(M.\\) :: M.IntMap a -> M.IntMap b -> M.IntMap a)
infixl 9 \\
null :: forall a. MonoidalIntMap a -> Bool
null :: MonoidalIntMap a -> Bool
null = (IntMap a -> Bool) -> MonoidalIntMap a -> Bool
coerce (IntMap a -> Bool
forall a. IntMap a -> Bool
M.null :: M.IntMap a -> Bool)
{-# INLINE null #-}
lookup :: forall a. Int -> MonoidalIntMap a -> Maybe a
lookup :: Int -> MonoidalIntMap a -> Maybe a
lookup = (Int -> IntMap a -> Maybe a) -> Int -> MonoidalIntMap a -> Maybe a
coerce (Int -> IntMap a -> Maybe a
forall a. Int -> IntMap a -> Maybe a
M.lookup :: Int -> M.IntMap a -> Maybe a)
{-# INLINE lookup #-}
lookupLT :: forall a. Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupLT :: Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupLT = (Int -> IntMap a -> Maybe (Int, a))
-> Int -> MonoidalIntMap a -> Maybe (Int, a)
coerce (Int -> IntMap a -> Maybe (Int, a)
forall a. Int -> IntMap a -> Maybe (Int, a)
M.lookupLT :: Int -> M.IntMap a -> Maybe (Int,a))
{-# INLINE lookupLT #-}
lookupGT :: forall a. Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupGT :: Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupGT = (Int -> IntMap a -> Maybe (Int, a))
-> Int -> MonoidalIntMap a -> Maybe (Int, a)
coerce (Int -> IntMap a -> Maybe (Int, a)
forall a. Int -> IntMap a -> Maybe (Int, a)
M.lookupGT :: Int -> M.IntMap a -> Maybe (Int,a))
{-# INLINE lookupGT #-}
lookupLE :: forall a. Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupLE :: Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupLE = (Int -> IntMap a -> Maybe (Int, a))
-> Int -> MonoidalIntMap a -> Maybe (Int, a)
coerce (Int -> IntMap a -> Maybe (Int, a)
forall a. Int -> IntMap a -> Maybe (Int, a)
M.lookupLE :: Int -> M.IntMap a -> Maybe (Int,a))
{-# INLINE lookupLE #-}
lookupGE :: forall a. Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupGE :: Int -> MonoidalIntMap a -> Maybe (Int, a)
lookupGE = (Int -> IntMap a -> Maybe (Int, a))
-> Int -> MonoidalIntMap a -> Maybe (Int, a)
coerce (Int -> IntMap a -> Maybe (Int, a)
forall a. Int -> IntMap a -> Maybe (Int, a)
M.lookupGE :: Int -> M.IntMap a -> Maybe (Int,a))
{-# INLINE lookupGE #-}
empty :: forall a. MonoidalIntMap a
empty :: MonoidalIntMap a
empty = IntMap a -> MonoidalIntMap a
coerce (IntMap a
forall a. IntMap a
M.empty :: M.IntMap a)
{-# INLINE empty #-}
insert :: forall a. Int -> a -> MonoidalIntMap a -> MonoidalIntMap a
insert :: Int -> a -> MonoidalIntMap a -> MonoidalIntMap a
insert = (Int -> a -> IntMap a -> IntMap a)
-> Int -> a -> MonoidalIntMap a -> MonoidalIntMap a
coerce (Int -> a -> IntMap a -> IntMap a
forall a. Int -> a -> IntMap a -> IntMap a
M.insert :: Int -> a -> M.IntMap a -> M.IntMap a)
{-# INLINE insert #-}
insertWith :: forall a. (a -> a -> a) -> Int -> a -> MonoidalIntMap a -> MonoidalIntMap a
insertWith :: (a -> a -> a) -> Int -> a -> MonoidalIntMap a -> MonoidalIntMap a
insertWith = ((a -> a -> a) -> Int -> a -> IntMap a -> IntMap a)
-> (a -> a -> a)
-> Int
-> a
-> MonoidalIntMap a
-> MonoidalIntMap a
coerce ((a -> a -> a) -> Int -> a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> Int -> a -> IntMap a -> IntMap a
M.insertWith :: (a -> a -> a) -> Int -> a -> M.IntMap a -> M.IntMap a)
{-# INLINE insertWith #-}
insertWithKey :: forall a. (Int -> a -> a -> a) -> Int -> a -> MonoidalIntMap a -> MonoidalIntMap a
insertWithKey :: (Int -> a -> a -> a)
-> Int -> a -> MonoidalIntMap a -> MonoidalIntMap a
insertWithKey = ((Int -> a -> a -> a) -> Int -> a -> IntMap a -> IntMap a)
-> (Int -> a -> a -> a)
-> Int
-> a
-> MonoidalIntMap a
-> MonoidalIntMap a
coerce ((Int -> a -> a -> a) -> Int -> a -> IntMap a -> IntMap a
forall a. (Int -> a -> a -> a) -> Int -> a -> IntMap a -> IntMap a
M.insertWithKey :: (Int -> a -> a -> a) -> Int -> a -> M.IntMap a -> M.IntMap a)
{-# INLINE insertWithKey #-}
insertLookupWithKey :: forall a. (Int -> a -> a -> a) -> Int -> a -> MonoidalIntMap a -> (Maybe a, MonoidalIntMap a)
insertLookupWithKey :: (Int -> a -> a -> a)
-> Int -> a -> MonoidalIntMap a -> (Maybe a, MonoidalIntMap a)
insertLookupWithKey = ((Int -> a -> a -> a)
-> Int -> a -> IntMap a -> (Maybe a, IntMap a))
-> (Int -> a -> a -> a)
-> Int
-> a
-> MonoidalIntMap a
-> (Maybe a, MonoidalIntMap a)
coerce ((Int -> a -> a -> a) -> Int -> a -> IntMap a -> (Maybe a, IntMap a)
forall a.
(Int -> a -> a -> a) -> Int -> a -> IntMap a -> (Maybe a, IntMap a)
M.insertLookupWithKey :: (Int -> a -> a -> a) -> Int -> a -> M.IntMap a -> (Maybe a, M.IntMap a))
{-# INLINE insertLookupWithKey #-}
adjust :: forall a. (a -> a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
adjust :: (a -> a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
adjust = ((a -> a) -> Int -> IntMap a -> IntMap a)
-> (a -> a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((a -> a) -> Int -> IntMap a -> IntMap a
forall a. (a -> a) -> Int -> IntMap a -> IntMap a
M.adjust :: (a -> a) -> Int -> M.IntMap a -> M.IntMap a)
{-# INLINE adjust #-}
adjustWithKey :: forall a. (Int -> a -> a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
adjustWithKey :: (Int -> a -> a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
adjustWithKey = ((Int -> a -> a) -> Int -> IntMap a -> IntMap a)
-> (Int -> a -> a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((Int -> a -> a) -> Int -> IntMap a -> IntMap a
forall a. (Int -> a -> a) -> Int -> IntMap a -> IntMap a
M.adjustWithKey :: (Int -> a -> a) -> Int -> M.IntMap a -> M.IntMap a)
{-# INLINE adjustWithKey #-}
update :: forall a. (a -> Maybe a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
update :: (a -> Maybe a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
update = ((a -> Maybe a) -> Int -> IntMap a -> IntMap a)
-> (a -> Maybe a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((a -> Maybe a) -> Int -> IntMap a -> IntMap a
forall a. (a -> Maybe a) -> Int -> IntMap a -> IntMap a
M.update :: (a -> Maybe a) -> Int -> M.IntMap a -> M.IntMap a)
{-# INLINE update #-}
updateWithKey :: forall a. (Int -> a -> Maybe a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
updateWithKey :: (Int -> a -> Maybe a)
-> Int -> MonoidalIntMap a -> MonoidalIntMap a
updateWithKey = ((Int -> a -> Maybe a) -> Int -> IntMap a -> IntMap a)
-> (Int -> a -> Maybe a)
-> Int
-> MonoidalIntMap a
-> MonoidalIntMap a
coerce ((Int -> a -> Maybe a) -> Int -> IntMap a -> IntMap a
forall a. (Int -> a -> Maybe a) -> Int -> IntMap a -> IntMap a
M.updateWithKey :: (Int -> a -> Maybe a) -> Int -> M.IntMap a -> M.IntMap a)
{-# INLINE updateWithKey #-}
updateLookupWithKey :: forall a. (Int -> a -> Maybe a) -> Int -> MonoidalIntMap a -> (Maybe a, MonoidalIntMap a)
updateLookupWithKey :: (Int -> a -> Maybe a)
-> Int -> MonoidalIntMap a -> (Maybe a, MonoidalIntMap a)
updateLookupWithKey = ((Int -> a -> Maybe a) -> Int -> IntMap a -> (Maybe a, IntMap a))
-> (Int -> a -> Maybe a)
-> Int
-> MonoidalIntMap a
-> (Maybe a, MonoidalIntMap a)
coerce ((Int -> a -> Maybe a) -> Int -> IntMap a -> (Maybe a, IntMap a)
forall a.
(Int -> a -> Maybe a) -> Int -> IntMap a -> (Maybe a, IntMap a)
M.updateLookupWithKey :: (Int -> a -> Maybe a) -> Int -> M.IntMap a -> (Maybe a, M.IntMap a))
{-# INLINE updateLookupWithKey #-}
alter :: forall a. (Maybe a -> Maybe a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
alter :: (Maybe a -> Maybe a) -> Int -> MonoidalIntMap a -> MonoidalIntMap a
alter = ((Maybe a -> Maybe a) -> Int -> IntMap a -> IntMap a)
-> (Maybe a -> Maybe a)
-> Int
-> MonoidalIntMap a
-> MonoidalIntMap a
coerce ((Maybe a -> Maybe a) -> Int -> IntMap a -> IntMap a
forall a. (Maybe a -> Maybe a) -> Int -> IntMap a -> IntMap a
M.alter :: (Maybe a -> Maybe a) -> Int -> M.IntMap a -> M.IntMap a)
{-# INLINE alter #-}
unionWith :: forall a. (a -> a -> a) -> MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
unionWith :: (a -> a -> a)
-> MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
unionWith = ((a -> a -> a) -> IntMap a -> IntMap a -> IntMap a)
-> (a -> a -> a)
-> MonoidalIntMap a
-> MonoidalIntMap a
-> MonoidalIntMap a
coerce ((a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWith :: (a -> a -> a) -> M.IntMap a -> M.IntMap a -> M.IntMap a)
{-# INLINE unionWith #-}
unionWithKey :: forall a. (Int -> a -> a -> a) -> MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
unionWithKey :: (Int -> a -> a -> a)
-> MonoidalIntMap a -> MonoidalIntMap a -> MonoidalIntMap a
unionWithKey = ((Int -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a)
-> (Int -> a -> a -> a)
-> MonoidalIntMap a
-> MonoidalIntMap a
-> MonoidalIntMap a
coerce ((Int -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
forall a. (Int -> a -> a -> a) -> IntMap a -> IntMap a -> IntMap a
M.unionWithKey :: (Int -> a -> a -> a) -> M.IntMap a -> M.IntMap a -> M.IntMap a)
{-# INLINE unionWithKey #-}
unionsWith :: forall a. (a -> a -> a) -> [MonoidalIntMap a] -> MonoidalIntMap a
unionsWith :: (a -> a -> a) -> [MonoidalIntMap a] -> MonoidalIntMap a
unionsWith = ((a -> a -> a) -> [IntMap a] -> IntMap a)
-> (a -> a -> a) -> [MonoidalIntMap a] -> MonoidalIntMap a
coerce ((a -> a -> a) -> [IntMap a] -> IntMap a
forall (f :: * -> *) a.
Foldable f =>
(a -> a -> a) -> f (IntMap a) -> IntMap a
M.unionsWith :: (a -> a -> a) -> [M.IntMap a] -> M.IntMap a)
{-# INLINE unionsWith #-}
difference :: forall a b. MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
difference :: MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
difference = MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
forall a b.
MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
(\\)
{-# INLINE difference #-}
differenceWith :: forall a b. (a -> b -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
differenceWith :: (a -> b -> Maybe a)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
differenceWith = ((a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a)
-> (a -> b -> Maybe a)
-> MonoidalIntMap a
-> MonoidalIntMap b
-> MonoidalIntMap a
coerce ((a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
forall a b. (a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
M.differenceWith :: (a -> b -> Maybe a) -> M.IntMap a -> M.IntMap b -> M.IntMap a)
{-# INLINE differenceWith #-}
differenceWithKey :: forall a b. (Int -> a -> b -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
differenceWithKey :: (Int -> a -> b -> Maybe a)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap a
differenceWithKey = ((Int -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a)
-> (Int -> a -> b -> Maybe a)
-> MonoidalIntMap a
-> MonoidalIntMap b
-> MonoidalIntMap a
coerce ((Int -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
forall a b.
(Int -> a -> b -> Maybe a) -> IntMap a -> IntMap b -> IntMap a
M.differenceWithKey :: (Int -> a -> b -> Maybe a) -> M.IntMap a -> M.IntMap b -> M.IntMap a)
{-# INLINE differenceWithKey #-}
intersectionWith :: forall a b c. (a -> b -> c) -> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
intersectionWith :: (a -> b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
intersectionWith = ((a -> b -> c) -> IntMap a -> IntMap b -> IntMap c)
-> (a -> b -> c)
-> MonoidalIntMap a
-> MonoidalIntMap b
-> MonoidalIntMap c
coerce ((a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c. (a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
M.intersectionWith :: (a -> b -> c) -> M.IntMap a -> M.IntMap b -> M.IntMap c)
{-# INLINE intersectionWith #-}
intersectionWithKey :: forall a b c. (Int -> a -> b -> c) -> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
intersectionWithKey :: (Int -> a -> b -> c)
-> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
intersectionWithKey = ((Int -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c)
-> (Int -> a -> b -> c)
-> MonoidalIntMap a
-> MonoidalIntMap b
-> MonoidalIntMap c
coerce ((Int -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
forall a b c.
(Int -> a -> b -> c) -> IntMap a -> IntMap b -> IntMap c
M.intersectionWithKey :: (Int -> a -> b -> c) -> M.IntMap a -> M.IntMap b -> M.IntMap c)
{-# INLINE intersectionWithKey #-}
mergeWithKey :: forall a b c. (Int -> a -> b -> Maybe c) -> (MonoidalIntMap a -> MonoidalIntMap c) -> (MonoidalIntMap b -> MonoidalIntMap c) -> MonoidalIntMap a -> MonoidalIntMap b -> MonoidalIntMap c
mergeWithKey :: (Int -> a -> b -> Maybe c)
-> (MonoidalIntMap a -> MonoidalIntMap c)
-> (MonoidalIntMap b -> MonoidalIntMap c)
-> MonoidalIntMap a
-> MonoidalIntMap b
-> MonoidalIntMap c
mergeWithKey = ((Int -> a -> b -> Maybe c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c)
-> (Int -> a -> b -> Maybe c)
-> (MonoidalIntMap a -> MonoidalIntMap c)
-> (MonoidalIntMap b -> MonoidalIntMap c)
-> MonoidalIntMap a
-> MonoidalIntMap b
-> MonoidalIntMap c
coerce ((Int -> a -> b -> Maybe c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
forall a b c.
(Int -> a -> b -> Maybe c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
M.mergeWithKey :: (Int -> a -> b -> Maybe c) -> (M.IntMap a -> M.IntMap c) -> (M.IntMap b -> M.IntMap c) -> M.IntMap a -> M.IntMap b -> M.IntMap c)
{-# INLINE mergeWithKey #-}
map :: (a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
map :: (a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
map = (a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap
{-# INLINE map #-}
mapWithKey :: forall a b. (Int -> a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
mapWithKey :: (Int -> a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
mapWithKey = ((Int -> a -> b) -> IntMap a -> IntMap b)
-> (Int -> a -> b) -> MonoidalIntMap a -> MonoidalIntMap b
coerce ((Int -> a -> b) -> IntMap a -> IntMap b
forall a b. (Int -> a -> b) -> IntMap a -> IntMap b
M.mapWithKey :: (Int -> a -> b) -> M.IntMap a -> M.IntMap b)
{-# INLINE mapWithKey #-}
traverseWithKey :: Applicative t => (Int -> a -> t b) -> MonoidalIntMap a -> t (MonoidalIntMap b)
traverseWithKey :: (Int -> a -> t b) -> MonoidalIntMap a -> t (MonoidalIntMap b)
traverseWithKey = (Int -> a -> t b) -> MonoidalIntMap a -> t (MonoidalIntMap b)
forall i (t :: * -> *) (f :: * -> *) a b.
(TraversableWithIndex i t, Applicative f) =>
(i -> a -> f b) -> t a -> f (t b)
itraverse
{-# INLINE traverseWithKey #-}
mapAccum :: forall a b c. (a -> b -> (a, c)) -> a -> MonoidalIntMap b -> (a, MonoidalIntMap c)
mapAccum :: (a -> b -> (a, c))
-> a -> MonoidalIntMap b -> (a, MonoidalIntMap c)
mapAccum = ((a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c))
-> (a -> b -> (a, c))
-> a
-> MonoidalIntMap b
-> (a, MonoidalIntMap c)
coerce ((a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
forall a b c. (a -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
M.mapAccum :: (a -> b -> (a, c)) -> a -> M.IntMap b -> (a, M.IntMap c))
{-# INLINE mapAccum #-}
mapAccumWithKey :: forall a b c. (a -> Int -> b -> (a, c)) -> a -> MonoidalIntMap b -> (a, MonoidalIntMap c)
mapAccumWithKey :: (a -> Int -> b -> (a, c))
-> a -> MonoidalIntMap b -> (a, MonoidalIntMap c)
mapAccumWithKey = ((a -> Int -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c))
-> (a -> Int -> b -> (a, c))
-> a
-> MonoidalIntMap b
-> (a, MonoidalIntMap c)
coerce ((a -> Int -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
forall a b c.
(a -> Int -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
M.mapAccumWithKey :: (a -> Int -> b -> (a, c)) -> a -> M.IntMap b -> (a, M.IntMap c))
{-# INLINE mapAccumWithKey #-}
mapAccumRWithKey :: forall a b c. (a -> Int -> b -> (a, c)) -> a -> MonoidalIntMap b -> (a, MonoidalIntMap c)
mapAccumRWithKey :: (a -> Int -> b -> (a, c))
-> a -> MonoidalIntMap b -> (a, MonoidalIntMap c)
mapAccumRWithKey = ((a -> Int -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c))
-> (a -> Int -> b -> (a, c))
-> a
-> MonoidalIntMap b
-> (a, MonoidalIntMap c)
coerce ((a -> Int -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
forall a b c.
(a -> Int -> b -> (a, c)) -> a -> IntMap b -> (a, IntMap c)
M.mapAccumRWithKey :: (a -> Int -> b -> (a, c)) -> a -> M.IntMap b -> (a, M.IntMap c))
{-# INLINE mapAccumRWithKey #-}
mapKeys :: forall a. (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
mapKeys :: (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
mapKeys = ((Int -> Int) -> IntMap a -> IntMap a)
-> (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((Int -> Int) -> IntMap a -> IntMap a
forall a. (Int -> Int) -> IntMap a -> IntMap a
M.mapKeys :: (Int -> Int) -> M.IntMap a -> M.IntMap a)
{-# INLINE mapKeys #-}
mapKeysWith :: forall a. (a -> a -> a) -> (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
mapKeysWith :: (a -> a -> a)
-> (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
mapKeysWith = ((a -> a -> a) -> (Int -> Int) -> IntMap a -> IntMap a)
-> (a -> a -> a)
-> (Int -> Int)
-> MonoidalIntMap a
-> MonoidalIntMap a
coerce ((a -> a -> a) -> (Int -> Int) -> IntMap a -> IntMap a
forall a. (a -> a -> a) -> (Int -> Int) -> IntMap a -> IntMap a
M.mapKeysWith :: (a -> a -> a) -> (Int -> Int) -> M.IntMap a -> M.IntMap a)
{-# INLINE mapKeysWith #-}
mapKeysMonotonic :: forall a. (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
mapKeysMonotonic :: (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
mapKeysMonotonic = ((Int -> Int) -> IntMap a -> IntMap a)
-> (Int -> Int) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((Int -> Int) -> IntMap a -> IntMap a
forall a. (Int -> Int) -> IntMap a -> IntMap a
M.mapKeysMonotonic :: (Int -> Int) -> M.IntMap a -> M.IntMap a)
{-# INLINE mapKeysMonotonic #-}
foldr :: forall a b. (a -> b -> b) -> b -> MonoidalIntMap a -> b
foldr :: (a -> b -> b) -> b -> MonoidalIntMap a -> b
foldr = ((a -> b -> b) -> b -> IntMap a -> b)
-> (a -> b -> b) -> b -> MonoidalIntMap a -> b
coerce ((a -> b -> b) -> b -> IntMap a -> b
forall a b. (a -> b -> b) -> b -> IntMap a -> b
M.foldr :: (a -> b -> b) -> b -> M.IntMap a -> b)
{-# INLINE foldr #-}
foldl :: forall a b. (a -> b -> a) -> a -> MonoidalIntMap b -> a
foldl :: (a -> b -> a) -> a -> MonoidalIntMap b -> a
foldl = ((a -> b -> a) -> a -> IntMap b -> a)
-> (a -> b -> a) -> a -> MonoidalIntMap b -> a
coerce ((a -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> b -> a) -> a -> IntMap b -> a
M.foldl :: (a -> b -> a) -> a -> M.IntMap b -> a)
{-# INLINE foldl #-}
foldrWithKey :: forall a b. (Int -> a -> b -> b) -> b -> MonoidalIntMap a -> b
foldrWithKey :: (Int -> a -> b -> b) -> b -> MonoidalIntMap a -> b
foldrWithKey = ((Int -> a -> b -> b) -> b -> IntMap a -> b)
-> (Int -> a -> b -> b) -> b -> MonoidalIntMap a -> b
coerce ((Int -> a -> b -> b) -> b -> IntMap a -> b
forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
M.foldrWithKey :: (Int -> a -> b -> b) -> b -> M.IntMap a -> b)
{-# INLINE foldrWithKey #-}
foldlWithKey :: forall a b. (a -> Int -> b -> a) -> a -> MonoidalIntMap b -> a
foldlWithKey :: (a -> Int -> b -> a) -> a -> MonoidalIntMap b -> a
foldlWithKey = ((a -> Int -> b -> a) -> a -> IntMap b -> a)
-> (a -> Int -> b -> a) -> a -> MonoidalIntMap b -> a
coerce ((a -> Int -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> Int -> b -> a) -> a -> IntMap b -> a
M.foldlWithKey :: (a -> Int -> b -> a) -> a -> M.IntMap b -> a)
{-# INLINE foldlWithKey #-}
foldMapWithKey :: forall a m. Monoid m => (Int -> a -> m) -> MonoidalIntMap a -> m
foldMapWithKey :: (Int -> a -> m) -> MonoidalIntMap a -> m
foldMapWithKey = ((Int -> a -> m) -> IntMap a -> m)
-> (Int -> a -> m) -> MonoidalIntMap a -> m
coerce (Monoid m => (Int -> a -> m) -> IntMap a -> m
forall m a. Monoid m => (Int -> a -> m) -> IntMap a -> m
M.foldMapWithKey :: Monoid m => (Int -> a -> m) -> M.IntMap a -> m)
{-# INLINE foldMapWithKey #-}
foldr' :: forall a b. (a -> b -> b) -> b -> MonoidalIntMap a -> b
foldr' :: (a -> b -> b) -> b -> MonoidalIntMap a -> b
foldr' = ((a -> b -> b) -> b -> IntMap a -> b)
-> (a -> b -> b) -> b -> MonoidalIntMap a -> b
coerce ((a -> b -> b) -> b -> IntMap a -> b
forall a b. (a -> b -> b) -> b -> IntMap a -> b
M.foldr' :: (a -> b -> b) -> b -> M.IntMap a -> b)
{-# INLINE foldr' #-}
foldl' :: forall a b. (a -> b -> a) -> a -> MonoidalIntMap b -> a
foldl' :: (a -> b -> a) -> a -> MonoidalIntMap b -> a
foldl' = ((a -> b -> a) -> a -> IntMap b -> a)
-> (a -> b -> a) -> a -> MonoidalIntMap b -> a
coerce ((a -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> b -> a) -> a -> IntMap b -> a
M.foldl' :: (a -> b -> a) -> a -> M.IntMap b -> a)
{-# INLINE foldl' #-}
foldrWithKey' :: forall a b. (Int -> a -> b -> b) -> b -> MonoidalIntMap a -> b
foldrWithKey' :: (Int -> a -> b -> b) -> b -> MonoidalIntMap a -> b
foldrWithKey' = ((Int -> a -> b -> b) -> b -> IntMap a -> b)
-> (Int -> a -> b -> b) -> b -> MonoidalIntMap a -> b
coerce ((Int -> a -> b -> b) -> b -> IntMap a -> b
forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
M.foldrWithKey' :: (Int -> a -> b -> b) -> b -> M.IntMap a -> b)
{-# INLINE foldrWithKey' #-}
foldlWithKey' :: forall a b. (a -> Int -> b -> a) -> a -> MonoidalIntMap b -> a
foldlWithKey' :: (a -> Int -> b -> a) -> a -> MonoidalIntMap b -> a
foldlWithKey' = ((a -> Int -> b -> a) -> a -> IntMap b -> a)
-> (a -> Int -> b -> a) -> a -> MonoidalIntMap b -> a
coerce ((a -> Int -> b -> a) -> a -> IntMap b -> a
forall a b. (a -> Int -> b -> a) -> a -> IntMap b -> a
M.foldlWithKey' :: (a -> Int -> b -> a) -> a -> M.IntMap b -> a)
{-# INLINE foldlWithKey' #-}
keysSet :: forall a. MonoidalIntMap a -> IntSet
keysSet :: MonoidalIntMap a -> IntSet
keysSet = (IntMap a -> IntSet) -> MonoidalIntMap a -> IntSet
coerce (IntMap a -> IntSet
forall a. IntMap a -> IntSet
M.keysSet :: M.IntMap a -> IntSet)
{-# INLINE keysSet #-}
fromSet :: forall a. (Int -> a) -> IntSet -> MonoidalIntMap a
fromSet :: (Int -> a) -> IntSet -> MonoidalIntMap a
fromSet = ((Int -> a) -> IntSet -> IntMap a)
-> (Int -> a) -> IntSet -> MonoidalIntMap a
coerce ((Int -> a) -> IntSet -> IntMap a
forall a. (Int -> a) -> IntSet -> IntMap a
M.fromSet :: (Int -> a) -> IntSet -> M.IntMap a)
{-# INLINE fromSet #-}
toList :: forall a. MonoidalIntMap a -> [(Int, a)]
toList :: MonoidalIntMap a -> [(Int, a)]
toList = (IntMap a -> [(Int, a)]) -> MonoidalIntMap a -> [(Int, a)]
coerce (IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
M.toList :: M.IntMap a -> [(Int, a)])
{-# INLINE toList #-}
fromList :: forall a. [(Int, a)] -> MonoidalIntMap a
fromList :: [(Int, a)] -> MonoidalIntMap a
fromList = ([(Int, a)] -> IntMap a) -> [(Int, a)] -> MonoidalIntMap a
coerce ([(Int, a)] -> IntMap a
forall a. [(Int, a)] -> IntMap a
M.fromList :: [(Int, a)] -> M.IntMap a)
{-# INLINE fromList #-}
fromListWith :: forall a. (a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromListWith :: (a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromListWith = ((a -> a -> a) -> [(Int, a)] -> IntMap a)
-> (a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
coerce ((a -> a -> a) -> [(Int, a)] -> IntMap a
forall a. (a -> a -> a) -> [(Int, a)] -> IntMap a
M.fromListWith :: (a -> a -> a) -> [(Int, a)] -> M.IntMap a)
{-# INLINE fromListWith #-}
fromListWithKey :: forall a. (Int -> a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromListWithKey :: (Int -> a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromListWithKey = ((Int -> a -> a -> a) -> [(Int, a)] -> IntMap a)
-> (Int -> a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
coerce ((Int -> a -> a -> a) -> [(Int, a)] -> IntMap a
forall a. (Int -> a -> a -> a) -> [(Int, a)] -> IntMap a
M.fromListWithKey :: (Int -> a -> a -> a) -> [(Int, a)] -> M.IntMap a)
{-# INLINE fromListWithKey #-}
toAscList :: forall a. MonoidalIntMap a -> [(Int, a)]
toAscList :: MonoidalIntMap a -> [(Int, a)]
toAscList = (IntMap a -> [(Int, a)]) -> MonoidalIntMap a -> [(Int, a)]
coerce (IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
M.toAscList :: M.IntMap a -> [(Int, a)])
{-# INLINE toAscList #-}
toDescList :: forall a. MonoidalIntMap a -> [(Int, a)]
toDescList :: MonoidalIntMap a -> [(Int, a)]
toDescList = (IntMap a -> [(Int, a)]) -> MonoidalIntMap a -> [(Int, a)]
coerce (IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
M.toDescList :: M.IntMap a -> [(Int, a)])
{-# INLINE toDescList #-}
fromAscList :: forall a. [(Int, a)] -> MonoidalIntMap a
fromAscList :: [(Int, a)] -> MonoidalIntMap a
fromAscList = ([(Int, a)] -> IntMap a) -> [(Int, a)] -> MonoidalIntMap a
coerce ([(Int, a)] -> IntMap a
forall a. [(Int, a)] -> IntMap a
M.fromAscList :: [(Int, a)] -> M.IntMap a)
{-# INLINE fromAscList #-}
fromAscListWith :: forall a. (a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromAscListWith :: (a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromAscListWith = ((a -> a -> a) -> [(Int, a)] -> IntMap a)
-> (a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
coerce ((a -> a -> a) -> [(Int, a)] -> IntMap a
forall a. (a -> a -> a) -> [(Int, a)] -> IntMap a
M.fromAscListWith :: (a -> a -> a) -> [(Int, a)] -> M.IntMap a)
{-# INLINE fromAscListWith #-}
fromAscListWithKey :: forall a. (Int -> a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromAscListWithKey :: (Int -> a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
fromAscListWithKey = ((Int -> a -> a -> a) -> [(Int, a)] -> IntMap a)
-> (Int -> a -> a -> a) -> [(Int, a)] -> MonoidalIntMap a
coerce ((Int -> a -> a -> a) -> [(Int, a)] -> IntMap a
forall a. (Int -> a -> a -> a) -> [(Int, a)] -> IntMap a
M.fromAscListWithKey :: (Int -> a -> a -> a) -> [(Int, a)] -> M.IntMap a)
{-# INLINE fromAscListWithKey #-}
fromDistinctAscList :: forall a. [(Int, a)] -> MonoidalIntMap a
fromDistinctAscList :: [(Int, a)] -> MonoidalIntMap a
fromDistinctAscList = ([(Int, a)] -> IntMap a) -> [(Int, a)] -> MonoidalIntMap a
coerce ([(Int, a)] -> IntMap a
forall a. [(Int, a)] -> IntMap a
M.fromDistinctAscList :: [(Int, a)] -> M.IntMap a)
{-# INLINE fromDistinctAscList #-}
fromDistinctList :: forall a. [(Int, a)] -> MonoidalIntMap a
fromDistinctList :: [(Int, a)] -> MonoidalIntMap a
fromDistinctList = ([(Int, a)] -> IntMap a) -> [(Int, a)] -> MonoidalIntMap a
coerce ([(Int, a)] -> IntMap a
forall a. [(Int, a)] -> IntMap a
M.fromList :: [(Int, a)] -> M.IntMap a)
{-# INLINE fromDistinctList #-}
filter :: forall a. (a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
filter :: (a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
filter = ((a -> Bool) -> IntMap a -> IntMap a)
-> (a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((a -> Bool) -> IntMap a -> IntMap a
forall a. (a -> Bool) -> IntMap a -> IntMap a
M.filter :: (a -> Bool) -> M.IntMap a -> M.IntMap a)
{-# INLINE filter #-}
filterWithKey :: forall a. (Int -> a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
filterWithKey :: (Int -> a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
filterWithKey = ((Int -> a -> Bool) -> IntMap a -> IntMap a)
-> (Int -> a -> Bool) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((Int -> a -> Bool) -> IntMap a -> IntMap a
forall a. (Int -> a -> Bool) -> IntMap a -> IntMap a
M.filterWithKey :: (Int -> a -> Bool) -> M.IntMap a -> M.IntMap a)
{-# INLINE filterWithKey #-}
partition :: forall a. (a -> Bool) -> MonoidalIntMap a -> (MonoidalIntMap a, MonoidalIntMap a)
partition :: (a -> Bool)
-> MonoidalIntMap a -> (MonoidalIntMap a, MonoidalIntMap a)
partition = ((a -> Bool) -> IntMap a -> (IntMap a, IntMap a))
-> (a -> Bool)
-> MonoidalIntMap a
-> (MonoidalIntMap a, MonoidalIntMap a)
coerce ((a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
forall a. (a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
M.partition :: (a -> Bool) -> M.IntMap a -> (M.IntMap a, M.IntMap a))
{-# INLINE partition #-}
partitionWithKey :: forall a. (Int -> a -> Bool) -> MonoidalIntMap a -> (MonoidalIntMap a, MonoidalIntMap a)
partitionWithKey :: (Int -> a -> Bool)
-> MonoidalIntMap a -> (MonoidalIntMap a, MonoidalIntMap a)
partitionWithKey = ((Int -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a))
-> (Int -> a -> Bool)
-> MonoidalIntMap a
-> (MonoidalIntMap a, MonoidalIntMap a)
coerce ((Int -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
forall a. (Int -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
M.partitionWithKey :: (Int -> a -> Bool) -> M.IntMap a -> (M.IntMap a, M.IntMap a))
{-# INLINE partitionWithKey #-}
mapMaybe :: forall a b. (a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
mapMaybe :: (a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
mapMaybe = ((a -> Maybe b) -> IntMap a -> IntMap b)
-> (a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
coerce ((a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (a -> Maybe b) -> IntMap a -> IntMap b
M.mapMaybe :: (a -> Maybe b) -> M.IntMap a -> M.IntMap b)
{-# INLINE mapMaybe #-}
mapMaybeWithKey :: forall a b. (Int -> a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
mapMaybeWithKey :: (Int -> a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
mapMaybeWithKey = ((Int -> a -> Maybe b) -> IntMap a -> IntMap b)
-> (Int -> a -> Maybe b) -> MonoidalIntMap a -> MonoidalIntMap b
coerce ((Int -> a -> Maybe b) -> IntMap a -> IntMap b
forall a b. (Int -> a -> Maybe b) -> IntMap a -> IntMap b
M.mapMaybeWithKey :: (Int -> a -> Maybe b) -> M.IntMap a -> M.IntMap b)
{-# INLINE mapMaybeWithKey #-}
mapEither :: forall a b c. (a -> Either b c) -> MonoidalIntMap a -> (MonoidalIntMap b, MonoidalIntMap c)
mapEither :: (a -> Either b c)
-> MonoidalIntMap a -> (MonoidalIntMap b, MonoidalIntMap c)
mapEither = ((a -> Either b c) -> IntMap a -> (IntMap b, IntMap c))
-> (a -> Either b c)
-> MonoidalIntMap a
-> (MonoidalIntMap b, MonoidalIntMap c)
coerce ((a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
forall a b c. (a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
M.mapEither :: (a -> Either b c) -> M.IntMap a -> (M.IntMap b, M.IntMap c))
{-# INLINE mapEither #-}
mapEitherWithKey :: forall a b c. (Int -> a -> Either b c) -> MonoidalIntMap a -> (MonoidalIntMap b, MonoidalIntMap c)
mapEitherWithKey :: (Int -> a -> Either b c)
-> MonoidalIntMap a -> (MonoidalIntMap b, MonoidalIntMap c)
mapEitherWithKey = ((Int -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c))
-> (Int -> a -> Either b c)
-> MonoidalIntMap a
-> (MonoidalIntMap b, MonoidalIntMap c)
coerce ((Int -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
forall a b c.
(Int -> a -> Either b c) -> IntMap a -> (IntMap b, IntMap c)
M.mapEitherWithKey :: (Int -> a -> Either b c) -> M.IntMap a -> (M.IntMap b, M.IntMap c))
{-# INLINE mapEitherWithKey #-}
split :: forall a. Int -> MonoidalIntMap a -> (MonoidalIntMap a, MonoidalIntMap a)
split :: Int -> MonoidalIntMap a -> (MonoidalIntMap a, MonoidalIntMap a)
split = (Int -> IntMap a -> (IntMap a, IntMap a))
-> Int -> MonoidalIntMap a -> (MonoidalIntMap a, MonoidalIntMap a)
coerce (Int -> IntMap a -> (IntMap a, IntMap a)
forall a. Int -> IntMap a -> (IntMap a, IntMap a)
M.split :: Int -> M.IntMap a -> (M.IntMap a, M.IntMap a))
{-# INLINE split #-}
splitLookup :: forall a. Int -> MonoidalIntMap a -> (MonoidalIntMap a, Maybe a, MonoidalIntMap a)
splitLookup :: Int
-> MonoidalIntMap a
-> (MonoidalIntMap a, Maybe a, MonoidalIntMap a)
splitLookup = (Int -> IntMap a -> (IntMap a, Maybe a, IntMap a))
-> Int
-> MonoidalIntMap a
-> (MonoidalIntMap a, Maybe a, MonoidalIntMap a)
coerce (Int -> IntMap a -> (IntMap a, Maybe a, IntMap a)
forall a. Int -> IntMap a -> (IntMap a, Maybe a, IntMap a)
M.splitLookup :: Int -> M.IntMap a -> (M.IntMap a, Maybe a, M.IntMap a))
{-# INLINE splitLookup #-}
splitRoot :: forall a. MonoidalIntMap a -> [MonoidalIntMap a]
splitRoot :: MonoidalIntMap a -> [MonoidalIntMap a]
splitRoot = (IntMap a -> [IntMap a]) -> MonoidalIntMap a -> [MonoidalIntMap a]
coerce (IntMap a -> [IntMap a]
forall a. IntMap a -> [IntMap a]
M.splitRoot :: M.IntMap a -> [M.IntMap a])
{-# INLINE splitRoot #-}
isSubmapOf :: forall a. Eq a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
isSubmapOf :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
isSubmapOf = (IntMap a -> IntMap a -> Bool)
-> MonoidalIntMap a -> MonoidalIntMap a -> Bool
coerce (IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
M.isSubmapOf :: M.IntMap a -> M.IntMap a -> Bool)
{-# INLINE isSubmapOf #-}
isSubmapOfBy :: forall a b. (a -> b -> Bool) -> MonoidalIntMap a -> MonoidalIntMap b -> Bool
isSubmapOfBy :: (a -> b -> Bool) -> MonoidalIntMap a -> MonoidalIntMap b -> Bool
isSubmapOfBy = ((a -> b -> Bool) -> IntMap a -> IntMap b -> Bool)
-> (a -> b -> Bool) -> MonoidalIntMap a -> MonoidalIntMap b -> Bool
coerce ((a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
M.isSubmapOfBy :: (a -> b -> Bool) -> M.IntMap a -> M.IntMap b -> Bool)
{-# INLINE isSubmapOfBy #-}
isProperSubmapOf :: forall a. Eq a => MonoidalIntMap a -> MonoidalIntMap a -> Bool
isProperSubmapOf :: MonoidalIntMap a -> MonoidalIntMap a -> Bool
isProperSubmapOf = (IntMap a -> IntMap a -> Bool)
-> MonoidalIntMap a -> MonoidalIntMap a -> Bool
coerce (IntMap a -> IntMap a -> Bool
forall a. Eq a => IntMap a -> IntMap a -> Bool
M.isProperSubmapOf :: M.IntMap a -> M.IntMap a -> Bool)
{-# INLINE isProperSubmapOf #-}
isProperSubmapOfBy :: forall a b. (a -> b -> Bool) -> MonoidalIntMap a -> MonoidalIntMap b -> Bool
isProperSubmapOfBy :: (a -> b -> Bool) -> MonoidalIntMap a -> MonoidalIntMap b -> Bool
isProperSubmapOfBy = ((a -> b -> Bool) -> IntMap a -> IntMap b -> Bool)
-> (a -> b -> Bool) -> MonoidalIntMap a -> MonoidalIntMap b -> Bool
coerce ((a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
M.isProperSubmapOfBy :: (a -> b -> Bool) -> M.IntMap a -> M.IntMap b -> Bool)
{-# INLINE isProperSubmapOfBy #-}
findMin :: forall a. MonoidalIntMap a -> (Int, a)
findMin :: MonoidalIntMap a -> (Int, a)
findMin = (IntMap a -> (Int, a)) -> MonoidalIntMap a -> (Int, a)
coerce (IntMap a -> (Int, a)
forall a. IntMap a -> (Int, a)
M.findMin :: M.IntMap a -> (Int, a))
{-# INLINE findMin #-}
findMax :: forall a. MonoidalIntMap a -> (Int, a)
findMax :: MonoidalIntMap a -> (Int, a)
findMax = (IntMap a -> (Int, a)) -> MonoidalIntMap a -> (Int, a)
coerce (IntMap a -> (Int, a)
forall a. IntMap a -> (Int, a)
M.findMax :: M.IntMap a -> (Int, a))
{-# INLINE findMax #-}
deleteMin :: forall a. MonoidalIntMap a -> MonoidalIntMap a
deleteMin :: MonoidalIntMap a -> MonoidalIntMap a
deleteMin = (IntMap a -> IntMap a) -> MonoidalIntMap a -> MonoidalIntMap a
coerce (IntMap a -> IntMap a
forall a. IntMap a -> IntMap a
M.deleteMin :: M.IntMap a -> M.IntMap a)
{-# INLINE deleteMin #-}
deleteMax :: forall a. MonoidalIntMap a -> MonoidalIntMap a
deleteMax :: MonoidalIntMap a -> MonoidalIntMap a
deleteMax = (IntMap a -> IntMap a) -> MonoidalIntMap a -> MonoidalIntMap a
coerce (IntMap a -> IntMap a
forall a. IntMap a -> IntMap a
M.deleteMax :: M.IntMap a -> M.IntMap a)
{-# INLINE deleteMax #-}
deleteFindMin :: forall a. MonoidalIntMap a -> ((Int, a), MonoidalIntMap a)
deleteFindMin :: MonoidalIntMap a -> ((Int, a), MonoidalIntMap a)
deleteFindMin = (IntMap a -> ((Int, a), IntMap a))
-> MonoidalIntMap a -> ((Int, a), MonoidalIntMap a)
coerce (IntMap a -> ((Int, a), IntMap a)
forall a. IntMap a -> ((Int, a), IntMap a)
M.deleteFindMin :: M.IntMap a -> ((Int, a), M.IntMap a))
{-# INLINE deleteFindMin #-}
deleteFindMax :: forall a. MonoidalIntMap a -> ((Int, a), MonoidalIntMap a)
deleteFindMax :: MonoidalIntMap a -> ((Int, a), MonoidalIntMap a)
deleteFindMax = (IntMap a -> ((Int, a), IntMap a))
-> MonoidalIntMap a -> ((Int, a), MonoidalIntMap a)
coerce (IntMap a -> ((Int, a), IntMap a)
forall a. IntMap a -> ((Int, a), IntMap a)
M.deleteFindMax :: M.IntMap a -> ((Int, a), M.IntMap a))
{-# INLINE deleteFindMax #-}
updateMin :: forall a. (a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMin :: (a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMin = ((a -> Maybe a) -> IntMap a -> IntMap a)
-> (a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((a -> Maybe a) -> IntMap a -> IntMap a
forall a. (a -> Maybe a) -> IntMap a -> IntMap a
M.updateMin :: (a -> Maybe a) -> M.IntMap a -> M.IntMap a)
{-# INLINE updateMin #-}
updateMax :: forall a. (a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMax :: (a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMax = ((a -> Maybe a) -> IntMap a -> IntMap a)
-> (a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((a -> Maybe a) -> IntMap a -> IntMap a
forall a. (a -> Maybe a) -> IntMap a -> IntMap a
M.updateMax :: (a -> Maybe a) -> M.IntMap a -> M.IntMap a)
{-# INLINE updateMax #-}
updateMinWithKey :: forall a. (Int -> a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMinWithKey :: (Int -> a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMinWithKey = ((Int -> a -> Maybe a) -> IntMap a -> IntMap a)
-> (Int -> a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((Int -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Int -> a -> Maybe a) -> IntMap a -> IntMap a
M.updateMinWithKey :: (Int -> a -> Maybe a) -> M.IntMap a -> M.IntMap a)
{-# INLINE updateMinWithKey #-}
updateMaxWithKey :: forall a. (Int -> a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMaxWithKey :: (Int -> a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
updateMaxWithKey = ((Int -> a -> Maybe a) -> IntMap a -> IntMap a)
-> (Int -> a -> Maybe a) -> MonoidalIntMap a -> MonoidalIntMap a
coerce ((Int -> a -> Maybe a) -> IntMap a -> IntMap a
forall a. (Int -> a -> Maybe a) -> IntMap a -> IntMap a
M.updateMaxWithKey :: (Int -> a -> Maybe a) -> M.IntMap a -> M.IntMap a)
{-# INLINE updateMaxWithKey #-}
minView :: forall a. MonoidalIntMap a -> Maybe (a, MonoidalIntMap a)
minView :: MonoidalIntMap a -> Maybe (a, MonoidalIntMap a)
minView = (IntMap a -> Maybe (a, IntMap a))
-> MonoidalIntMap a -> Maybe (a, MonoidalIntMap a)
coerce (IntMap a -> Maybe (a, IntMap a)
forall a. IntMap a -> Maybe (a, IntMap a)
M.minView :: M.IntMap a -> Maybe (a, M.IntMap a))
{-# INLINE minView #-}
maxView :: forall a. MonoidalIntMap a -> Maybe (a, MonoidalIntMap a)
maxView :: MonoidalIntMap a -> Maybe (a, MonoidalIntMap a)
maxView = (IntMap a -> Maybe (a, IntMap a))
-> MonoidalIntMap a -> Maybe (a, MonoidalIntMap a)
coerce (IntMap a -> Maybe (a, IntMap a)
forall a. IntMap a -> Maybe (a, IntMap a)
M.maxView :: M.IntMap a -> Maybe (a, M.IntMap a))
{-# INLINE maxView #-}
minViewWithKey :: forall a. MonoidalIntMap a -> Maybe ((Int, a), MonoidalIntMap a)
minViewWithKey :: MonoidalIntMap a -> Maybe ((Int, a), MonoidalIntMap a)
minViewWithKey = (IntMap a -> Maybe ((Int, a), IntMap a))
-> MonoidalIntMap a -> Maybe ((Int, a), MonoidalIntMap a)
coerce (IntMap a -> Maybe ((Int, a), IntMap a)
forall a. IntMap a -> Maybe ((Int, a), IntMap a)
M.minViewWithKey :: M.IntMap a -> Maybe ((Int, a), M.IntMap a))
{-# INLINE minViewWithKey #-}
maxViewWithKey :: forall a. MonoidalIntMap a -> Maybe ((Int, a), MonoidalIntMap a)
maxViewWithKey :: MonoidalIntMap a -> Maybe ((Int, a), MonoidalIntMap a)
maxViewWithKey = (IntMap a -> Maybe ((Int, a), IntMap a))
-> MonoidalIntMap a -> Maybe ((Int, a), MonoidalIntMap a)
coerce (IntMap a -> Maybe ((Int, a), IntMap a)
forall a. IntMap a -> Maybe ((Int, a), IntMap a)
M.maxViewWithKey :: M.IntMap a -> Maybe ((Int, a), M.IntMap a))
{-# INLINE maxViewWithKey #-}