{-# LANGUAGE CPP #-}
{-# LANGUAGE UndecidableInstances #-}
module Data.IntMap.Common.Refined where
import Control.Monad.Reader
import Control.DeepSeq
import Data.Coerce
import Data.Constraint (Dict(..))
import Data.Container.Refined.Proofs
import Data.Container.Refined.Unsafe
import Data.Distributive
import Data.Foldable.WithIndex
import Data.Functor.Rep
import Data.Functor.WithIndex
import qualified Data.Hashable as Hashable
import qualified Data.IntMap as IntMap
import Data.Proxy
import Data.Reflection
import Data.Traversable.WithIndex
import Data.Type.Coercion
import Data.Type.Equality ((:~:)(..))
import Refined
import Refined.Unsafe
import Unsafe.Coerce
#if MIN_VERSION_containers(0, 6, 7)
#elif MIN_VERSION_containers(0, 6, 2)
import qualified Data.List as List
#elif MIN_VERSION_containers(0, 5, 8)
import Data.Functor.Const (Const(..))
import qualified Data.List as List
import Data.Monoid (Any(..))
import qualified Data.IntMap.Merge.Lazy as IntMap
#else
import qualified Data.IntMap.Strict as IntMapStrict
import qualified Data.List as List
#endif
newtype IntMap s a = IntMap (IntMap.IntMap a)
deriving newtype (IntMap s a -> IntMap s a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall s a. Eq a => IntMap s a -> IntMap s a -> Bool
/= :: IntMap s a -> IntMap s a -> Bool
$c/= :: forall s a. Eq a => IntMap s a -> IntMap s a -> Bool
== :: IntMap s a -> IntMap s a -> Bool
$c== :: forall s a. Eq a => IntMap s a -> IntMap s a -> Bool
Eq, IntMap s a -> IntMap s a -> Bool
IntMap s a -> IntMap s a -> Ordering
IntMap s a -> IntMap s a -> IntMap s 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 {s} {a}. Ord a => Eq (IntMap s a)
forall s a. Ord a => IntMap s a -> IntMap s a -> Bool
forall s a. Ord a => IntMap s a -> IntMap s a -> Ordering
forall s a. Ord a => IntMap s a -> IntMap s a -> IntMap s a
min :: IntMap s a -> IntMap s a -> IntMap s a
$cmin :: forall s a. Ord a => IntMap s a -> IntMap s a -> IntMap s a
max :: IntMap s a -> IntMap s a -> IntMap s a
$cmax :: forall s a. Ord a => IntMap s a -> IntMap s a -> IntMap s a
>= :: IntMap s a -> IntMap s a -> Bool
$c>= :: forall s a. Ord a => IntMap s a -> IntMap s a -> Bool
> :: IntMap s a -> IntMap s a -> Bool
$c> :: forall s a. Ord a => IntMap s a -> IntMap s a -> Bool
<= :: IntMap s a -> IntMap s a -> Bool
$c<= :: forall s a. Ord a => IntMap s a -> IntMap s a -> Bool
< :: IntMap s a -> IntMap s a -> Bool
$c< :: forall s a. Ord a => IntMap s a -> IntMap s a -> Bool
compare :: IntMap s a -> IntMap s a -> Ordering
$ccompare :: forall s a. Ord a => IntMap s a -> IntMap s a -> Ordering
Ord, Int -> IntMap s a -> ShowS
[IntMap s a] -> ShowS
IntMap s a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall s a. Show a => Int -> IntMap s a -> ShowS
forall s a. Show a => [IntMap s a] -> ShowS
forall s a. Show a => IntMap s a -> String
showList :: [IntMap s a] -> ShowS
$cshowList :: forall s a. Show a => [IntMap s a] -> ShowS
show :: IntMap s a -> String
$cshow :: forall s a. Show a => IntMap s a -> String
showsPrec :: Int -> IntMap s a -> ShowS
$cshowsPrec :: forall s a. Show a => Int -> IntMap s a -> ShowS
Show, forall a b. a -> IntMap s b -> IntMap s a
forall a b. (a -> b) -> IntMap s a -> IntMap s b
forall s a b. a -> IntMap s b -> IntMap s a
forall s a b. (a -> b) -> IntMap s a -> IntMap s b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: forall a b. a -> IntMap s b -> IntMap s a
$c<$ :: forall s a b. a -> IntMap s b -> IntMap s a
fmap :: forall a b. (a -> b) -> IntMap s a -> IntMap s b
$cfmap :: forall s a b. (a -> b) -> IntMap s a -> IntMap s b
Functor, forall a. Eq a => a -> IntMap s a -> Bool
forall a. Num a => IntMap s a -> a
forall a. Ord a => IntMap s a -> a
forall m. Monoid m => IntMap s m -> m
forall a. IntMap s a -> Bool
forall a. IntMap s a -> Int
forall a. IntMap s a -> [a]
forall a. (a -> a -> a) -> IntMap s a -> a
forall s a. Eq a => a -> IntMap s a -> Bool
forall s a. Num a => IntMap s a -> a
forall s a. Ord a => IntMap s a -> a
forall m a. Monoid m => (a -> m) -> IntMap s a -> m
forall s m. Monoid m => IntMap s m -> m
forall s a. IntMap s a -> Bool
forall s a. IntMap s a -> Int
forall s a. IntMap s a -> [a]
forall b a. (b -> a -> b) -> b -> IntMap s a -> b
forall a b. (a -> b -> b) -> b -> IntMap s a -> b
forall s a. (a -> a -> a) -> IntMap s a -> a
forall s m a. Monoid m => (a -> m) -> IntMap s a -> m
forall s b a. (b -> a -> b) -> b -> IntMap s a -> b
forall s a b. (a -> b -> b) -> b -> IntMap s 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 :: forall a. Num a => IntMap s a -> a
$cproduct :: forall s a. Num a => IntMap s a -> a
sum :: forall a. Num a => IntMap s a -> a
$csum :: forall s a. Num a => IntMap s a -> a
minimum :: forall a. Ord a => IntMap s a -> a
$cminimum :: forall s a. Ord a => IntMap s a -> a
maximum :: forall a. Ord a => IntMap s a -> a
$cmaximum :: forall s a. Ord a => IntMap s a -> a
elem :: forall a. Eq a => a -> IntMap s a -> Bool
$celem :: forall s a. Eq a => a -> IntMap s a -> Bool
length :: forall a. IntMap s a -> Int
$clength :: forall s a. IntMap s a -> Int
null :: forall a. IntMap s a -> Bool
$cnull :: forall s a. IntMap s a -> Bool
toList :: forall a. IntMap s a -> [a]
$ctoList :: forall s a. IntMap s a -> [a]
foldl1 :: forall a. (a -> a -> a) -> IntMap s a -> a
$cfoldl1 :: forall s a. (a -> a -> a) -> IntMap s a -> a
foldr1 :: forall a. (a -> a -> a) -> IntMap s a -> a
$cfoldr1 :: forall s a. (a -> a -> a) -> IntMap s a -> a
foldl' :: forall b a. (b -> a -> b) -> b -> IntMap s a -> b
$cfoldl' :: forall s b a. (b -> a -> b) -> b -> IntMap s a -> b
foldl :: forall b a. (b -> a -> b) -> b -> IntMap s a -> b
$cfoldl :: forall s b a. (b -> a -> b) -> b -> IntMap s a -> b
foldr' :: forall a b. (a -> b -> b) -> b -> IntMap s a -> b
$cfoldr' :: forall s a b. (a -> b -> b) -> b -> IntMap s a -> b
foldr :: forall a b. (a -> b -> b) -> b -> IntMap s a -> b
$cfoldr :: forall s a b. (a -> b -> b) -> b -> IntMap s a -> b
foldMap' :: forall m a. Monoid m => (a -> m) -> IntMap s a -> m
$cfoldMap' :: forall s m a. Monoid m => (a -> m) -> IntMap s a -> m
foldMap :: forall m a. Monoid m => (a -> m) -> IntMap s a -> m
$cfoldMap :: forall s m a. Monoid m => (a -> m) -> IntMap s a -> m
fold :: forall m. Monoid m => IntMap s m -> m
$cfold :: forall s m. Monoid m => IntMap s m -> m
Foldable, IntMap s a -> ()
forall a. (a -> ()) -> NFData a
forall s a. NFData a => IntMap s a -> ()
rnf :: IntMap s a -> ()
$crnf :: forall s a. NFData a => IntMap s a -> ()
NFData)
#if MIN_VERSION_hashable(1, 3, 4)
deriving newtype (Int -> IntMap s a -> Int
IntMap s a -> Int
forall a. Eq a -> (Int -> a -> Int) -> (a -> Int) -> Hashable a
forall {s} {a}. Hashable a => Eq (IntMap s a)
forall s a. Hashable a => Int -> IntMap s a -> Int
forall s a. Hashable a => IntMap s a -> Int
hash :: IntMap s a -> Int
$chash :: forall s a. Hashable a => IntMap s a -> Int
hashWithSalt :: Int -> IntMap s a -> Int
$chashWithSalt :: forall s a. Hashable a => Int -> IntMap s a -> Int
Hashable.Hashable)
#endif
deriving stock (forall s. Functor (IntMap s)
forall s. Foldable (IntMap s)
forall s (m :: * -> *) a.
Monad m =>
IntMap s (m a) -> m (IntMap s a)
forall s (f :: * -> *) a.
Applicative f =>
IntMap s (f a) -> f (IntMap s a)
forall s (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IntMap s a -> m (IntMap s b)
forall s (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IntMap s a -> f (IntMap s 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 (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IntMap s a -> f (IntMap s b)
sequence :: forall (m :: * -> *) a. Monad m => IntMap s (m a) -> m (IntMap s a)
$csequence :: forall s (m :: * -> *) a.
Monad m =>
IntMap s (m a) -> m (IntMap s a)
mapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IntMap s a -> m (IntMap s b)
$cmapM :: forall s (m :: * -> *) a b.
Monad m =>
(a -> m b) -> IntMap s a -> m (IntMap s b)
sequenceA :: forall (f :: * -> *) a.
Applicative f =>
IntMap s (f a) -> f (IntMap s a)
$csequenceA :: forall s (f :: * -> *) a.
Applicative f =>
IntMap s (f a) -> f (IntMap s a)
traverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IntMap s a -> f (IntMap s b)
$ctraverse :: forall s (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> IntMap s a -> f (IntMap s b)
Traversable)
type role IntMap nominal representational
toIntMap :: forall s a. IntMap s a -> IntMap.IntMap a
toIntMap :: forall s a. IntMap s a -> IntMap a
toIntMap (IntMap IntMap a
m) = IntMap a
m
type Key s = Refined (InSet 'Int s) Int
unsafeCastKey :: forall s. Coercion Int (Key s)
unsafeCastKey :: forall s. Coercion Int (Key s)
unsafeCastKey = forall {k} x (p :: k). Coercion x (Refined p x)
reallyUnsafeUnderlyingRefined
unsafeKey :: Int -> Key s
unsafeKey :: forall s. Int -> Key s
unsafeKey = forall a b. Coercion a b -> a -> b
coerceWith forall s. Coercion Int (Key s)
unsafeCastKey
data SomeIntMap a where
SomeIntMap :: forall s a. !(IntMap s a) -> SomeIntMap a
withIntMap :: forall a r. SomeIntMap a -> (forall s. IntMap s a -> r) -> r
withIntMap :: forall a r. SomeIntMap a -> (forall s. IntMap s a -> r) -> r
withIntMap (SomeIntMap IntMap s a
m) forall s. IntMap s a -> r
k = forall s. IntMap s a -> r
k IntMap s a
m
fromIntMap :: forall a. IntMap.IntMap a -> SomeIntMap a
fromIntMap :: forall a. IntMap a -> SomeIntMap a
fromIntMap IntMap a
m = forall s a. IntMap s a -> SomeIntMap a
SomeIntMap (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m)
data SomeIntMapWith p a where
SomeIntMapWith :: forall s a p. !(IntMap s a) -> !(p s) -> SomeIntMapWith p a
withIntMapWith
:: forall a r p. SomeIntMapWith p a -> (forall s. IntMap s a -> p s -> r) -> r
withIntMapWith :: forall a r (p :: * -> *).
SomeIntMapWith p a -> (forall s. IntMap s a -> p s -> r) -> r
withIntMapWith (SomeIntMapWith IntMap s a
m p s
p) forall s. IntMap s a -> p s -> r
k = forall s. IntMap s a -> p s -> r
k IntMap s a
m p s
p
data Some2IntMapWith p a b where
Some2IntMapWith
:: forall s t a b p. !(IntMap s a)
-> !(IntMap t b)
-> !(p s t)
-> Some2IntMapWith p a b
with2IntMapWith
:: forall a b r p. Some2IntMapWith p a b
-> (forall s t. IntMap s a -> IntMap t b -> p s t -> r)
-> r
with2IntMapWith :: forall a b r (p :: * -> * -> *).
Some2IntMapWith p a b
-> (forall s t. IntMap s a -> IntMap t b -> p s t -> r) -> r
with2IntMapWith (Some2IntMapWith IntMap s a
m1 IntMap t b
m2 p s t
p) forall s t. IntMap s a -> IntMap t b -> p s t -> r
k = forall s t. IntMap s a -> IntMap t b -> p s t -> r
k IntMap s a
m1 IntMap t b
m2 p s t
p
empty :: forall a. SomeIntMapWith (EmptyProof 'Int) a
empty :: forall a. SomeIntMapWith (EmptyProof 'Int) a
empty = forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith (forall s a. IntMap a -> IntMap s a
IntMap forall a. IntMap a
IntMap.empty) forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) r.
(forall s. InSet f r :-> InSet f s) -> EmptyProof f r
EmptyProof forall p q. p :-> q
unsafeSubset
fromSet :: forall s a. KnownIntSet s => (Key s -> a) -> IntMap s a
fromSet :: forall s a. KnownIntSet s => (Key s -> a) -> IntMap s a
fromSet Key s -> a
f = forall s a. IntMap a -> IntMap s a
IntMap forall a b. (a -> b) -> a -> b
$ forall a. (Int -> a) -> IntSet -> IntMap a
IntMap.fromSet (Key s -> a
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Int -> Key s
unsafeKey) (forall {k} (s :: k) a (proxy :: k -> *).
Reifies s a =>
proxy s -> a
reflect forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @s)
delete :: forall s a. Int -> IntMap s a -> SomeIntMapWith (SupersetProof 'Int s) a
delete :: forall s a.
Int -> IntMap s a -> SomeIntMapWith (SupersetProof 'Int s) a
delete Int
k (IntMap IntMap a
m) = forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith (forall s a. IntMap a -> IntMap s a
IntMap forall a b. (a -> b) -> a -> b
$ forall a. Int -> IntMap a -> IntMap a
IntMap.delete Int
k IntMap a
m)
forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s r.
(InSet f r :-> InSet f s) -> SupersetProof f s r
SupersetProof forall p q. p :-> q
unsafeSubset
lookup :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookup :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookup Int
k (IntMap IntMap a
m) = (forall s. Int -> Key s
unsafeKey Int
k,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. Int -> IntMap a -> Maybe a
IntMap.lookup Int
k IntMap a
m
(!) :: forall s a. IntMap s a -> Key s -> a
! :: forall s a. IntMap s a -> Key s -> a
(!) (IntMap IntMap a
m) Key s
k = case forall a. Int -> IntMap a -> Maybe a
IntMap.lookup (forall {k} (p :: k) x. Refined p x -> x
unrefine Key s
k) IntMap a
m of
Maybe a
Nothing -> forall a. HasCallStack => String -> a
error String
"(!): bug: Data.IntMap.Refined has been subverted"
Just a
x -> a
x
member :: forall s a. Int -> IntMap s a -> Maybe (Key s)
member :: forall s a. Int -> IntMap s a -> Maybe (Key s)
member Int
k (IntMap IntMap a
m)
| Int
k forall a. Int -> IntMap a -> Bool
`IntMap.member` IntMap a
m = forall a. a -> Maybe a
Just (forall s. Int -> Key s
unsafeKey Int
k)
| Bool
otherwise = forall a. Maybe a
Nothing
lookupLT :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupLT :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupLT = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall a. Int -> IntMap a -> Maybe (Int, a)
IntMap.lookupLT @a
lookupGT :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupGT :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupGT = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall a. Int -> IntMap a -> Maybe (Int, a)
IntMap.lookupGT @a
lookupLE :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupLE :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupLE = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall a. Int -> IntMap a -> Maybe (Int, a)
IntMap.lookupLE @a
lookupGE :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupGE :: forall s a. Int -> IntMap s a -> Maybe (Key s, a)
lookupGE = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall a. Int -> IntMap a -> Maybe (Int, a)
IntMap.lookupGE @a
null :: forall s a. IntMap s a -> Maybe (EmptyProof 'Int s)
null :: forall s a. IntMap s a -> Maybe (EmptyProof 'Int s)
null (IntMap IntMap a
m)
| forall a. IntMap a -> Bool
IntMap.null IntMap a
m = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) r.
(forall s. InSet f r :-> InSet f s) -> EmptyProof f r
EmptyProof forall p q. p :-> q
unsafeSubset
| Bool
otherwise = forall a. Maybe a
Nothing
isSubmapOfBy
:: forall s t a b. (a -> b -> Bool)
-> IntMap s a
-> IntMap t b
-> Maybe (SubsetProof 'Int s t)
isSubmapOfBy :: forall s t a b.
(a -> b -> Bool)
-> IntMap s a -> IntMap t b -> Maybe (SubsetProof 'Int s t)
isSubmapOfBy a -> b -> Bool
f (IntMap IntMap a
m1) (IntMap IntMap b
m2)
| forall a b. (a -> b -> Bool) -> IntMap a -> IntMap b -> Bool
IntMap.isSubmapOfBy a -> b -> Bool
f IntMap a
m1 IntMap b
m2 = forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s r.
(InSet f s :-> InSet f r) -> SubsetProof f s r
SubsetProof forall p q. p :-> q
unsafeSubset
| Bool
otherwise = forall a. Maybe a
Nothing
disjoint
:: forall s t a b. IntMap s a -> IntMap t b -> Maybe (DisjointProof 'Int s t)
disjoint :: forall s t a b.
IntMap s a -> IntMap t b -> Maybe (DisjointProof 'Int s t)
disjoint (IntMap IntMap a
m1) (IntMap IntMap b
m2)
#if MIN_VERSION_containers(0, 6, 2)
| forall a b. IntMap a -> IntMap b -> Bool
IntMap.disjoint IntMap a
m1 IntMap b
m2
#elif MIN_VERSION_containers(0, 5, 8)
| Const (Any False) <- IntMap.mergeA
(IntMap.traverseMissing \_ _ -> Const mempty)
(IntMap.traverseMissing \_ _ -> Const mempty)
(IntMap.zipWithAMatched \_ _ _ -> Const $ Any True)
m1
m2
#else
| IntMap.null $ IntMapStrict.intersectionWith (\_ _ -> ()) m1 m2
#endif
= forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s r.
(forall t.
(InSet f t :-> InSet f s)
-> (InSet f t :-> InSet f r) -> forall u. InSet f t :-> InSet f u)
-> DisjointProof f s r
DisjointProof \InSet 'Int t :-> InSet 'Int s
f InSet 'Int t :-> InSet 'Int t
g -> forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 InSet 'Int t :-> InSet 'Int s
f InSet 'Int t :-> InSet 'Int t
g
| Bool
otherwise = forall a. Maybe a
Nothing
zipWithKey
:: forall s a b c. (Key s -> a -> b -> c)
-> IntMap s a
-> IntMap s b
-> IntMap s c
zipWithKey :: forall s a b c.
(Key s -> a -> b -> c) -> IntMap s a -> IntMap s b -> IntMap s c
zipWithKey Key s -> a -> b -> c
f (IntMap IntMap a
m1) (IntMap IntMap b
m2) = forall s a. IntMap a -> IntMap s a
IntMap
forall a b. (a -> b) -> a -> b
$ forall a b c.
(Int -> a -> b -> Maybe c)
-> (IntMap a -> IntMap c)
-> (IntMap b -> IntMap c)
-> IntMap a
-> IntMap b
-> IntMap c
IntMap.mergeWithKey (\Int
k a
x b
y -> forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$ Key s -> a -> b -> c
f (forall s. Int -> Key s
unsafeKey Int
k) a
x b
y)
(\IntMap a
m -> if forall a. IntMap a -> Bool
IntMap.null IntMap a
m
then forall a. IntMap a
IntMap.empty
else forall a. HasCallStack => String -> a
error String
"zipWithKey: bug: Data.IntMap.Refined has been subverted")
(\IntMap b
m -> if forall a. IntMap a -> Bool
IntMap.null IntMap b
m
then forall a. IntMap a
IntMap.empty
else forall a. HasCallStack => String -> a
error String
"zipWithKey: bug: Data.IntMap.Refined has been subverted")
IntMap a
m1
IntMap b
m2
difference
:: forall s t a b. IntMap s a
-> IntMap t b
-> SomeIntMapWith (DifferenceProof 'Int s t) a
difference :: forall s t a b.
IntMap s a
-> IntMap t b -> SomeIntMapWith (DifferenceProof 'Int s t) a
difference (IntMap IntMap a
m1) (IntMap IntMap b
m2) = forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith
(forall s a. IntMap a -> IntMap s a
IntMap forall a b. (a -> b) -> a -> b
$ forall a b. IntMap a -> IntMap b -> IntMap a
IntMap.difference IntMap a
m1 IntMap b
m2)
forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s t r.
(InSet f r :-> InSet f s)
-> (forall u.
(InSet f u :-> InSet f r)
-> (InSet f u :-> InSet f t) -> forall v. InSet f u :-> InSet f v)
-> (InSet f s :-> (InSet f t || InSet f r))
-> DifferenceProof f s t r
DifferenceProof forall p q. p :-> q
unsafeSubset (\InSet 'Int u :-> InSet 'Int Any
f InSet 'Int u :-> InSet 'Int t
g -> forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 InSet 'Int u :-> InSet 'Int Any
f InSet 'Int u :-> InSet 'Int t
g) forall p q. p :-> q
unsafeSubset
mapWithKey :: forall s a b. (Key s -> a -> b) -> IntMap s a -> IntMap s b
mapWithKey :: forall s a b. (Key s -> a -> b) -> IntMap s a -> IntMap s b
mapWithKey = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce
forall a b. (a -> b) -> a -> b
$ forall a b. (Int -> a -> b) -> IntMap a -> IntMap b
IntMap.mapWithKey @a @b
traverseWithKey
:: forall s f a b. Applicative f
=> (Key s -> a -> f b) -> IntMap s a -> f (IntMap s b)
traverseWithKey :: forall s (f :: * -> *) a b.
Applicative f =>
(Key s -> a -> f b) -> IntMap s a -> f (IntMap s b)
traverseWithKey Key s -> a -> f b
f (IntMap IntMap a
m) = forall s a. IntMap a -> IntMap s a
IntMap forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (t :: * -> *) a b.
Applicative t =>
(Int -> a -> t b) -> IntMap a -> t (IntMap b)
IntMap.traverseWithKey (Key s -> a -> f b
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Int -> Key s
unsafeKey) IntMap a
m
foldMapWithKey
:: forall s a m. Monoid m => (Key s -> a -> m) -> IntMap s a -> m
foldMapWithKey :: forall s a m. Monoid m => (Key s -> a -> m) -> IntMap s a -> m
foldMapWithKey = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce
forall a b. (a -> b) -> a -> b
$ forall m a. Monoid m => (Int -> a -> m) -> IntMap a -> m
IntMap.foldMapWithKey @m @a
foldrWithKey :: forall s a b. (Key s -> a -> b -> b) -> b -> IntMap s a -> b
foldrWithKey :: forall s a b. (Key s -> a -> b -> b) -> b -> IntMap s a -> b
foldrWithKey = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce
forall a b. (a -> b) -> a -> b
$ forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
IntMap.foldrWithKey @a @b
foldlWithKey :: forall s a b. (b -> Key s -> a -> b) -> b -> IntMap s a -> b
foldlWithKey :: forall s a b. (b -> Key s -> a -> b) -> b -> IntMap s a -> b
foldlWithKey = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce
forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Int -> b -> a) -> a -> IntMap b -> a
IntMap.foldlWithKey @b @a
foldrWithKey' :: forall s a b. (Key s -> a -> b -> b) -> b -> IntMap s a -> b
foldrWithKey' :: forall s a b. (Key s -> a -> b -> b) -> b -> IntMap s a -> b
foldrWithKey' = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce
forall a b. (a -> b) -> a -> b
$ forall a b. (Int -> a -> b -> b) -> b -> IntMap a -> b
IntMap.foldrWithKey' @a @b
foldlWithKey' :: forall s a b. (b -> Key s -> a -> b) -> b -> IntMap s a -> b
foldlWithKey' :: forall s a b. (b -> Key s -> a -> b) -> b -> IntMap s a -> b
foldlWithKey' = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce
forall a b. (a -> b) -> a -> b
$ forall a b. (a -> Int -> b -> a) -> a -> IntMap b -> a
IntMap.foldlWithKey' @b @a
keysSet :: forall s a. IntMap s a -> IntSet s
keysSet :: forall s a. IntMap s a -> IntSet s
keysSet (IntMap IntMap a
m) = forall a r. a -> (forall s. Reifies s a => Proxy s -> r) -> r
reify (forall a. IntMap a -> IntSet
IntMap.keysSet IntMap a
m)
\(Proxy s
_ :: Proxy s') -> case forall a b. a -> b
unsafeCoerce forall {k} (a :: k). a :~: a
Refl :: s :~: s' of
s :~: s
Refl -> forall (a :: Constraint). a => Dict a
Dict
toList :: forall s a. IntMap s a -> [(Key s, a)]
toList :: forall s a. IntMap s a -> [(Key s, a)]
toList = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall a. IntMap a -> [(Int, a)]
IntMap.toAscList @a
toDescList :: forall s a. IntMap s a -> [(Key s, a)]
toDescList :: forall s a. IntMap s a -> [(Key s, a)]
toDescList = forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce forall a b. (a -> b) -> a -> b
$ forall a. IntMap a -> [(Int, a)]
IntMap.toDescList @a
filterWithKey
:: forall s a. (Key s -> a -> Bool)
-> IntMap s a
-> SomeIntMapWith (SupersetProof 'Int s) a
filterWithKey :: forall s a.
(Key s -> a -> Bool)
-> IntMap s a -> SomeIntMapWith (SupersetProof 'Int s) a
filterWithKey Key s -> a -> Bool
p (IntMap IntMap a
m)
= forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith (forall s a. IntMap a -> IntMap s a
IntMap forall a b. (a -> b) -> a -> b
$ forall a. (Int -> a -> Bool) -> IntMap a -> IntMap a
IntMap.filterWithKey (Key s -> a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Int -> Key s
unsafeKey) IntMap a
m)
forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s r.
(InSet f r :-> InSet f s) -> SupersetProof f s r
SupersetProof forall p q. p :-> q
unsafeSubset
restrictKeys
:: forall s t a. KnownIntSet t
=> IntMap s a -> SomeIntMapWith (IntersectionProof 'Int s t) a
restrictKeys :: forall s t a.
KnownIntSet t =>
IntMap s a -> SomeIntMapWith (IntersectionProof 'Int s t) a
restrictKeys (IntMap IntMap a
m) = forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith
#if MIN_VERSION_containers(0, 5, 8)
(forall s a. IntMap a -> IntMap s a
IntMap forall a b. (a -> b) -> a -> b
$ forall a. IntMap a -> IntSet -> IntMap a
IntMap.restrictKeys IntMap a
m forall a b. (a -> b) -> a -> b
$ forall {k} (s :: k) a (proxy :: k -> *).
Reifies s a =>
proxy s -> a
reflect forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @t)
#else
(IntMap $ IntMap.intersectionWith const m
$ IntMap.fromSet id $ reflect $ Proxy @t)
#endif
forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s t r.
(InSet f r :-> (InSet f s && InSet f t))
-> (forall u.
(InSet f u :-> InSet f s)
-> (InSet f u :-> InSet f t) -> InSet f u :-> InSet f r)
-> IntersectionProof f s t r
IntersectionProof forall p q. p :-> q
unsafeSubset forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2
withoutKeys
:: forall s t a. KnownIntSet t
=> IntMap s a -> SomeIntMapWith (DifferenceProof 'Int s t) a
withoutKeys :: forall s t a.
KnownIntSet t =>
IntMap s a -> SomeIntMapWith (DifferenceProof 'Int s t) a
withoutKeys (IntMap IntMap a
m) = forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith
#if MIN_VERSION_containers(0, 5, 8)
(forall s a. IntMap a -> IntMap s a
IntMap forall a b. (a -> b) -> a -> b
$ forall a. IntMap a -> IntSet -> IntMap a
IntMap.withoutKeys IntMap a
m forall a b. (a -> b) -> a -> b
$ forall {k} (s :: k) a (proxy :: k -> *).
Reifies s a =>
proxy s -> a
reflect forall a b. (a -> b) -> a -> b
$ forall {k} (t :: k). Proxy t
Proxy @t)
#else
(IntMap $ IntMap.difference m $ IntMap.fromSet id $ reflect $ Proxy @t)
#endif
forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s t r.
(InSet f r :-> InSet f s)
-> (forall u.
(InSet f u :-> InSet f r)
-> (InSet f u :-> InSet f t) -> forall v. InSet f u :-> InSet f v)
-> (InSet f s :-> (InSet f t || InSet f r))
-> DifferenceProof f s t r
DifferenceProof forall p q. p :-> q
unsafeSubset (\InSet 'Int u :-> InSet 'Int Any
f InSet 'Int u :-> InSet 'Int t
g -> forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 InSet 'Int u :-> InSet 'Int Any
f InSet 'Int u :-> InSet 'Int t
g) forall p q. p :-> q
unsafeSubset
partitionWithKey
:: forall s a. (Key s -> a -> Bool)
-> IntMap s a
-> Some2IntMapWith (PartitionProof 'Int s Int) a a
partitionWithKey :: forall s a.
(Key s -> a -> Bool)
-> IntMap s a -> Some2IntMapWith (PartitionProof 'Int s Int) a a
partitionWithKey Key s -> a -> Bool
p (IntMap IntMap a
m)
= case forall a. (Int -> a -> Bool) -> IntMap a -> (IntMap a, IntMap a)
IntMap.partitionWithKey (Key s -> a -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Int -> Key s
unsafeKey) IntMap a
m of
(IntMap a
m1, IntMap a
m2) -> forall s t a b (p :: * -> * -> *).
IntMap s a -> IntMap t b -> p s t -> Some2IntMapWith p a b
Some2IntMapWith (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m1) (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m2) forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s a r q.
(Refined (InSet f s) a
-> Either (Refined (InSet f r) a) (Refined (InSet f q) a))
-> ((InSet f r || InSet f q) :-> InSet f s)
-> (forall t.
(InSet f r :-> InSet f t)
-> (InSet f q :-> InSet f t) -> InSet f s :-> InSet f t)
-> (forall t.
(InSet f t :-> InSet f r)
-> (InSet f t :-> InSet f q) -> forall u. InSet f t :-> InSet f u)
-> PartitionProof f s a r q
PartitionProof
do \Key s
k -> case forall a. Int -> IntMap a -> Maybe a
IntMap.lookup (forall {k} (p :: k) x. Refined p x -> x
unrefine Key s
k) IntMap a
m of
Maybe a
Nothing -> forall a. HasCallStack => String -> a
error
String
"partitionWithKey: bug: Data.IntMap.Refined has been subverted"
Just a
x -> if Key s -> a -> Bool
p Key s
k a
x
then forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall s. Int -> Key s
unsafeKey forall a b. (a -> b) -> a -> b
$ forall {k} (p :: k) x. Refined p x -> x
unrefine Key s
k
else forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ forall s. Int -> Key s
unsafeKey forall a b. (a -> b) -> a -> b
$ forall {k} (p :: k) x. Refined p x -> x
unrefine Key s
k
forall p q. p :-> q
unsafeSubset forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 \InSet 'Int t :-> InSet 'Int Any
f InSet 'Int t :-> InSet 'Int Any
g -> forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 InSet 'Int t :-> InSet 'Int Any
f InSet 'Int t :-> InSet 'Int Any
g
spanAntitone
:: forall s a. (Key s -> Bool)
-> IntMap s a
-> Some2IntMapWith (PartialPartitionProof 'Int s) a a
spanAntitone :: forall s a.
(Key s -> Bool)
-> IntMap s a -> Some2IntMapWith (PartialPartitionProof 'Int s) a a
spanAntitone Key s -> Bool
p (IntMap IntMap a
m) =
#if MIN_VERSION_containers(0, 6, 7)
case IntMap.spanAntitone (p . unsafeKey) m of
(m1, m2)
#else
case forall a. (a -> Bool) -> [a] -> ([a], [a])
List.span (Key s -> Bool
p forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall s. Int -> Key s
unsafeKey forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a, b) -> a
fst) forall a b. (a -> b) -> a -> b
$ forall a. IntMap a -> [(Int, a)]
IntMap.toAscList IntMap a
m of
([(Int, a)]
xs1, [(Int, a)]
xs2)
| let m1 :: IntMap a
m1 = forall a. [(Int, a)] -> IntMap a
IntMap.fromDistinctAscList [(Int, a)]
xs1
, let m2 :: IntMap a
m2 = forall a. [(Int, a)] -> IntMap a
IntMap.fromDistinctAscList [(Int, a)]
xs2
#endif
-> forall s t a b (p :: * -> * -> *).
IntMap s a -> IntMap t b -> p s t -> Some2IntMapWith p a b
Some2IntMapWith (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m1) (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m2) forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s r q.
((InSet f r || InSet f q) :-> InSet f s)
-> (forall t.
(InSet f r :-> InSet f t)
-> (InSet f q :-> InSet f t) -> InSet f s :-> InSet f t)
-> (forall t.
(InSet f t :-> InSet f r)
-> (InSet f t :-> InSet f q) -> forall u. InSet f t :-> InSet f u)
-> PartialPartitionProof f s r q
PartialPartitionProof
forall p q. p :-> q
unsafeSubset forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 \InSet 'Int t :-> InSet 'Int Any
f InSet 'Int t :-> InSet 'Int Any
g -> forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 InSet 'Int t :-> InSet 'Int Any
f InSet 'Int t :-> InSet 'Int Any
g
splitLookup
:: forall s a. Int
-> IntMap s a
-> Some2IntMapWith (SplitProof 'Int s (Key s, a)) a a
splitLookup :: forall s a.
Int
-> IntMap s a -> Some2IntMapWith (SplitProof 'Int s (Key s, a)) a a
splitLookup Int
k (IntMap IntMap a
m) = case forall a. Int -> IntMap a -> (IntMap a, Maybe a, IntMap a)
IntMap.splitLookup Int
k IntMap a
m of
(IntMap a
m1, Maybe a
v, IntMap a
m2) -> forall s t a b (p :: * -> * -> *).
IntMap s a -> IntMap t b -> p s t -> Some2IntMapWith p a b
Some2IntMapWith (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m1) (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m2) forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s e r q.
Maybe e
-> ((InSet f r || InSet f q) :-> InSet f s)
-> (forall t.
(InSet f t :-> InSet f r)
-> (InSet f t :-> InSet f q) -> forall u. InSet f t :-> InSet f u)
-> SplitProof f s e r q
SplitProof
((forall s. Int -> Key s
unsafeKey Int
k,) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Maybe a
v) forall p q. p :-> q
unsafeSubset \InSet 'Int t :-> InSet 'Int Any
f InSet 'Int t :-> InSet 'Int Any
g -> forall p' q' p'' q'' p q. (p' :-> q') -> (p'' :-> q'') -> p :-> q
unsafeSubsetWith2 InSet 'Int t :-> InSet 'Int Any
f InSet 'Int t :-> InSet 'Int Any
g
minViewWithKey
:: forall s a. IntMap s a
-> Either
(EmptyProof 'Int s)
((Key s, a), SomeIntMapWith (SupersetProof 'Int s) a)
minViewWithKey :: forall s a.
IntMap s a
-> Either
(EmptyProof 'Int s)
((Key s, a), SomeIntMapWith (SupersetProof 'Int s) a)
minViewWithKey (IntMap IntMap a
m) = case forall a. IntMap a -> Maybe ((Int, a), IntMap a)
IntMap.minViewWithKey IntMap a
m of
Maybe ((Int, a), IntMap a)
Nothing -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) r.
(forall s. InSet f r :-> InSet f s) -> EmptyProof f r
EmptyProof forall p q. p :-> q
unsafeSubset
Just ((Int, a)
kv, IntMap a
m') -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ (forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce (Int, a)
kv,)
forall a b. (a -> b) -> a -> b
$ forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m') forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s r.
(InSet f r :-> InSet f s) -> SupersetProof f s r
SupersetProof forall p q. p :-> q
unsafeSubset
maxViewWithKey
:: forall s a. IntMap s a
-> Either
(EmptyProof 'Int s)
((Key s, a), SomeIntMapWith (SupersetProof 'Int s) a)
maxViewWithKey :: forall s a.
IntMap s a
-> Either
(EmptyProof 'Int s)
((Key s, a), SomeIntMapWith (SupersetProof 'Int s) a)
maxViewWithKey (IntMap IntMap a
m) = case forall a. IntMap a -> Maybe ((Int, a), IntMap a)
IntMap.maxViewWithKey IntMap a
m of
Maybe ((Int, a), IntMap a)
Nothing -> forall a b. a -> Either a b
Left forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) r.
(forall s. InSet f r :-> InSet f s) -> EmptyProof f r
EmptyProof forall p q. p :-> q
unsafeSubset
Just ((Int, a)
kv, IntMap a
m') -> forall a b. b -> Either a b
Right forall a b. (a -> b) -> a -> b
$ (forall {k} (a :: k) (b :: k) r.
Coercion a b -> (Coercible a b => r) -> r
gcoerceWith (forall s. Coercion Int (Key s)
unsafeCastKey @s) forall a b. (a -> b) -> a -> b
$ coerce :: forall a b. Coercible a b => a -> b
coerce (Int, a)
kv,)
forall a b. (a -> b) -> a -> b
$ forall s a (p :: * -> *). IntMap s a -> p s -> SomeIntMapWith p a
SomeIntMapWith (forall s a. IntMap a -> IntMap s a
IntMap IntMap a
m') forall a b. (a -> b) -> a -> b
$ forall (f :: Flavor) s r.
(InSet f r :-> InSet f s) -> SupersetProof f s r
SupersetProof forall p q. p :-> q
unsafeSubset
castKey
:: forall s t k.
(forall x. Refined (InSet 'Int s) x -> Refined (InSet 'Int t) x)
-> (forall x. Refined (InSet 'Int t) x -> Refined (InSet 'Int s) x)
-> Coercion (Refined (InSet 'Int s) k) (Refined (InSet 'Int t) k)
castKey :: forall s t k.
(forall x. Refined (InSet 'Int s) x -> Refined (InSet 'Int t) x)
-> (forall x. Refined (InSet 'Int t) x -> Refined (InSet 'Int s) x)
-> Coercion (Refined (InSet 'Int s) k) (Refined (InSet 'Int t) k)
castKey = forall a p q.
(p :-> q) -> (q :-> p) -> Coercion (Refined p a) (Refined q a)
castRefined
cast
:: forall s t k. (forall x. Coercion
(Refined (InSet 'Int s) x)
(Refined (InSet 'Int t) x))
-> Coercion (IntMap s k) (IntMap t k)
cast :: forall s t k.
(forall x.
Coercion (Refined (InSet 'Int s) x) (Refined (InSet 'Int t) x))
-> Coercion (IntMap s k) (IntMap t k)
cast Coercion (Refined (InSet 'Int s) Any) (Refined (InSet 'Int t) Any)
forall x.
Coercion (Refined (InSet 'Int s) x) (Refined (InSet 'Int t) x)
Coercion = forall {k} (a :: k) (b :: k). Coercible a b => Coercion a b
Coercion
instance FunctorWithIndex (Key s) (IntMap s) where
imap :: forall a b. (Key s -> a -> b) -> IntMap s a -> IntMap s b
imap = forall s a b. (Key s -> a -> b) -> IntMap s a -> IntMap s b
mapWithKey
instance FoldableWithIndex (Key s) (IntMap s) where
ifoldMap :: forall m a. Monoid m => (Key s -> a -> m) -> IntMap s a -> m
ifoldMap = forall s a m. Monoid m => (Key s -> a -> m) -> IntMap s a -> m
foldMapWithKey
instance TraversableWithIndex (Key s) (IntMap s) where
itraverse :: forall (f :: * -> *) a b.
Applicative f =>
(Key s -> a -> f b) -> IntMap s a -> f (IntMap s b)
itraverse = forall s (f :: * -> *) a b.
Applicative f =>
(Key s -> a -> f b) -> IntMap s a -> f (IntMap s b)
traverseWithKey
instance KnownIntSet s => Applicative (IntMap s) where
pure :: forall a. a -> IntMap s a
pure a
x = forall s a. KnownIntSet s => (Key s -> a) -> IntMap s a
fromSet \Key s
_ -> a
x
<*> :: forall a b. IntMap s (a -> b) -> IntMap s a -> IntMap s b
(<*>) = forall s a b c.
(Key s -> a -> b -> c) -> IntMap s a -> IntMap s b -> IntMap s c
zipWithKey (forall a b. a -> b -> a
const forall a. a -> a
id)
bind :: forall s a b. IntMap s a -> (a -> IntMap s b) -> IntMap s b
bind :: forall s a b. IntMap s a -> (a -> IntMap s b) -> IntMap s b
bind IntMap s a
m a -> IntMap s b
f = forall s a b. (Key s -> a -> b) -> IntMap s a -> IntMap s b
mapWithKey (\Key s
k a
x -> a -> IntMap s b
f a
x forall s a. IntMap s a -> Key s -> a
! Key s
k) IntMap s a
m
instance KnownIntSet s => Monad (IntMap s) where
>>= :: forall a b. IntMap s a -> (a -> IntMap s b) -> IntMap s b
(>>=) = forall s a b. IntMap s a -> (a -> IntMap s b) -> IntMap s b
bind
instance KnownIntSet s => MonadReader (Key s) (IntMap s) where
ask :: IntMap s (Key s)
ask = forall s a. KnownIntSet s => (Key s -> a) -> IntMap s a
fromSet forall a. a -> a
id
local :: forall a. (Key s -> Key s) -> IntMap s a -> IntMap s a
local Key s -> Key s
f IntMap s a
m = forall s a b. (Key s -> a -> b) -> IntMap s a -> IntMap s b
mapWithKey (\Key s
k a
_ -> IntMap s a
m forall s a. IntMap s a -> Key s -> a
! Key s -> Key s
f Key s
k) IntMap s a
m
instance Semigroup a => Semigroup (IntMap s a) where
<> :: IntMap s a -> IntMap s a -> IntMap s a
(<>) = forall s a b c.
(Key s -> a -> b -> c) -> IntMap s a -> IntMap s b -> IntMap s c
zipWithKey (forall a b. a -> b -> a
const forall a. Semigroup a => a -> a -> a
(<>))
instance (KnownIntSet s, Monoid a) => Monoid (IntMap s a) where
mempty :: IntMap s a
mempty = forall s a. KnownIntSet s => (Key s -> a) -> IntMap s a
fromSet \Key s
_ -> forall a. Monoid a => a
mempty
instance KnownIntSet s => Distributive (IntMap s) where
collect :: forall (f :: * -> *) a b.
Functor f =>
(a -> IntMap s b) -> f a -> IntMap s (f b)
collect = forall (f :: * -> *) (w :: * -> *) a b.
(Representable f, Functor w) =>
(a -> f b) -> w a -> f (w b)
collectRep
distribute :: forall (f :: * -> *) a.
Functor f =>
f (IntMap s a) -> IntMap s (f a)
distribute = forall (f :: * -> *) (w :: * -> *) a.
(Representable f, Functor w) =>
w (f a) -> f (w a)
distributeRep
instance KnownIntSet s => Representable (IntMap s) where
type Rep (IntMap s) = Key s
index :: forall a. IntMap s a -> Rep (IntMap s) -> a
index = forall s a. IntMap s a -> Key s -> a
(!)
tabulate :: forall a. (Rep (IntMap s) -> a) -> IntMap s a
tabulate = forall s a. KnownIntSet s => (Key s -> a) -> IntMap s a
fromSet
#if MIN_VERSION_hashable(1, 3, 4)
#else
instance Hashable.Hashable a => Hashable.Hashable (IntMap s a) where
hashWithSalt s (IntMap m) = IntMap.foldlWithKey'
(\s' k v -> Hashable.hashWithSalt (Hashable.hashWithSalt s' k) v)
(Hashable.hashWithSalt s (IntMap.size m))
m
#endif