{-# LANGUAGE DerivingStrategies #-}
{-# LANGUAGE PatternSynonyms #-}
{-# LANGUAGE ViewPatterns #-}
module Development.IDE.Graph.Internal.Key
( Key
, KeyValue (..)
, pattern Key
, newKey
, renderKey
, KeyMap
, mapKeyMap
, insertKeyMap
, lookupKeyMap
, lookupDefaultKeyMap
, fromListKeyMap
, fromListWithKeyMap
, toListKeyMap
, elemsKeyMap
, restrictKeysKeyMap
, KeySet
, nullKeySet
, insertKeySet
, memberKeySet
, toListKeySet
, lengthKeySet
, filterKeySet
, singletonKeySet
, fromListKeySet
, deleteKeySet
, differenceKeySet
) where
import Data.Coerce
import Data.Dynamic
import qualified Data.HashMap.Strict as Map
import Data.IntMap (IntMap)
import qualified Data.IntMap.Strict as IM
import Data.IntSet (IntSet)
import qualified Data.IntSet as IS
import Data.IORef
import Data.Text (Text)
import qualified Data.Text as T
import Data.Typeable
import Development.IDE.Graph.Classes
import System.IO.Unsafe
newtype Key = UnsafeMkKey Int
pattern Key :: () => (Typeable a, Hashable a, Show a) => a -> Key
pattern $mKey :: forall {r}.
Key
-> (forall {a}. (Typeable a, Hashable a, Show a) => a -> r)
-> ((# #) -> r)
-> r
Key a <- (lookupKeyValue -> KeyValue a _)
{-# COMPLETE Key #-}
data KeyValue = forall a . (Typeable a, Hashable a, Show a) => KeyValue a Text
instance Eq KeyValue where
KeyValue a
a Text
_ == :: KeyValue -> KeyValue -> Bool
== KeyValue a
b Text
_ = a -> Maybe a
forall a. a -> Maybe a
Just a
a Maybe a -> Maybe a -> Bool
forall a. Eq a => a -> a -> Bool
== a -> Maybe a
forall a b. (Typeable a, Typeable b) => a -> Maybe b
cast a
b
instance Hashable KeyValue where
hashWithSalt :: Int -> KeyValue -> Int
hashWithSalt Int
i (KeyValue a
x Text
_) = Int -> (TypeRep, a) -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
i (a -> TypeRep
forall a. Typeable a => a -> TypeRep
typeOf a
x, a
x)
instance Show KeyValue where
show :: KeyValue -> String
show (KeyValue a
_ Text
t) = Text -> String
T.unpack Text
t
data GlobalKeyValueMap = GlobalKeyValueMap !(Map.HashMap KeyValue Key) !(IntMap KeyValue) {-# UNPACK #-} !Int
keyMap :: IORef GlobalKeyValueMap
keyMap :: IORef GlobalKeyValueMap
keyMap = IO (IORef GlobalKeyValueMap) -> IORef GlobalKeyValueMap
forall a. IO a -> a
unsafePerformIO (IO (IORef GlobalKeyValueMap) -> IORef GlobalKeyValueMap)
-> IO (IORef GlobalKeyValueMap) -> IORef GlobalKeyValueMap
forall a b. (a -> b) -> a -> b
$ GlobalKeyValueMap -> IO (IORef GlobalKeyValueMap)
forall a. a -> IO (IORef a)
newIORef (HashMap KeyValue Key -> IntMap KeyValue -> Int -> GlobalKeyValueMap
GlobalKeyValueMap HashMap KeyValue Key
forall k v. HashMap k v
Map.empty IntMap KeyValue
forall a. IntMap a
IM.empty Int
0)
{-# NOINLINE keyMap #-}
newKey :: (Typeable a, Hashable a, Show a) => a -> Key
newKey :: forall a. (Typeable a, Hashable a, Show a) => a -> Key
newKey a
k = IO Key -> Key
forall a. IO a -> a
unsafePerformIO (IO Key -> Key) -> IO Key -> Key
forall a b. (a -> b) -> a -> b
$ do
let !newKey :: KeyValue
newKey = a -> Text -> KeyValue
forall a. (Typeable a, Hashable a, Show a) => a -> Text -> KeyValue
KeyValue a
k (String -> Text
T.pack (a -> String
forall a. Show a => a -> String
show a
k))
IORef GlobalKeyValueMap
-> (GlobalKeyValueMap -> (GlobalKeyValueMap, Key)) -> IO Key
forall a b. IORef a -> (a -> (a, b)) -> IO b
atomicModifyIORef' IORef GlobalKeyValueMap
keyMap ((GlobalKeyValueMap -> (GlobalKeyValueMap, Key)) -> IO Key)
-> (GlobalKeyValueMap -> (GlobalKeyValueMap, Key)) -> IO Key
forall a b. (a -> b) -> a -> b
$ \km :: GlobalKeyValueMap
km@(GlobalKeyValueMap HashMap KeyValue Key
hm IntMap KeyValue
im Int
n) ->
let new_key :: Maybe Key
new_key = KeyValue -> HashMap KeyValue Key -> Maybe Key
forall k v. (Eq k, Hashable k) => k -> HashMap k v -> Maybe v
Map.lookup KeyValue
newKey HashMap KeyValue Key
hm
in case Maybe Key
new_key of
Just Key
v -> (GlobalKeyValueMap
km, Key
v)
Maybe Key
Nothing ->
let !new_index :: Key
new_index = Int -> Key
UnsafeMkKey Int
n
in (HashMap KeyValue Key -> IntMap KeyValue -> Int -> GlobalKeyValueMap
GlobalKeyValueMap (KeyValue -> Key -> HashMap KeyValue Key -> HashMap KeyValue Key
forall k v.
(Eq k, Hashable k) =>
k -> v -> HashMap k v -> HashMap k v
Map.insert KeyValue
newKey Key
new_index HashMap KeyValue Key
hm) (Int -> KeyValue -> IntMap KeyValue -> IntMap KeyValue
forall a. Int -> a -> IntMap a -> IntMap a
IM.insert Int
n KeyValue
newKey IntMap KeyValue
im) (Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
+Int
1), Key
new_index)
{-# NOINLINE newKey #-}
lookupKeyValue :: Key -> KeyValue
lookupKeyValue :: Key -> KeyValue
lookupKeyValue (UnsafeMkKey Int
x) = IO KeyValue -> KeyValue
forall a. IO a -> a
unsafePerformIO (IO KeyValue -> KeyValue) -> IO KeyValue -> KeyValue
forall a b. (a -> b) -> a -> b
$ do
GlobalKeyValueMap HashMap KeyValue Key
_ IntMap KeyValue
im Int
_ <- IORef GlobalKeyValueMap -> IO GlobalKeyValueMap
forall a. IORef a -> IO a
readIORef IORef GlobalKeyValueMap
keyMap
KeyValue -> IO KeyValue
forall a. a -> IO a
forall (f :: * -> *) a. Applicative f => a -> f a
pure (KeyValue -> IO KeyValue) -> KeyValue -> IO KeyValue
forall a b. (a -> b) -> a -> b
$! IntMap KeyValue
im IntMap KeyValue -> Int -> KeyValue
forall a. IntMap a -> Int -> a
IM.! Int
x
{-# NOINLINE lookupKeyValue #-}
instance Eq Key where
UnsafeMkKey Int
a == :: Key -> Key -> Bool
== UnsafeMkKey Int
b = Int
a Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
b
instance Hashable Key where
hashWithSalt :: Int -> Key -> Int
hashWithSalt Int
i (UnsafeMkKey Int
x) = Int -> Int -> Int
forall a. Hashable a => Int -> a -> Int
hashWithSalt Int
i Int
x
instance Show Key where
show :: Key -> String
show (Key a
x) = a -> String
forall a. Show a => a -> String
show a
x
renderKey :: Key -> Text
renderKey :: Key -> Text
renderKey (Key -> KeyValue
lookupKeyValue -> KeyValue a
_ Text
t) = Text
t
newtype KeySet = KeySet IntSet
deriving newtype (KeySet -> KeySet -> Bool
(KeySet -> KeySet -> Bool)
-> (KeySet -> KeySet -> Bool) -> Eq KeySet
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: KeySet -> KeySet -> Bool
== :: KeySet -> KeySet -> Bool
$c/= :: KeySet -> KeySet -> Bool
/= :: KeySet -> KeySet -> Bool
Eq, Eq KeySet
Eq KeySet =>
(KeySet -> KeySet -> Ordering)
-> (KeySet -> KeySet -> Bool)
-> (KeySet -> KeySet -> Bool)
-> (KeySet -> KeySet -> Bool)
-> (KeySet -> KeySet -> Bool)
-> (KeySet -> KeySet -> KeySet)
-> (KeySet -> KeySet -> KeySet)
-> Ord KeySet
KeySet -> KeySet -> Bool
KeySet -> KeySet -> Ordering
KeySet -> KeySet -> KeySet
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
$ccompare :: KeySet -> KeySet -> Ordering
compare :: KeySet -> KeySet -> Ordering
$c< :: KeySet -> KeySet -> Bool
< :: KeySet -> KeySet -> Bool
$c<= :: KeySet -> KeySet -> Bool
<= :: KeySet -> KeySet -> Bool
$c> :: KeySet -> KeySet -> Bool
> :: KeySet -> KeySet -> Bool
$c>= :: KeySet -> KeySet -> Bool
>= :: KeySet -> KeySet -> Bool
$cmax :: KeySet -> KeySet -> KeySet
max :: KeySet -> KeySet -> KeySet
$cmin :: KeySet -> KeySet -> KeySet
min :: KeySet -> KeySet -> KeySet
Ord, NonEmpty KeySet -> KeySet
KeySet -> KeySet -> KeySet
(KeySet -> KeySet -> KeySet)
-> (NonEmpty KeySet -> KeySet)
-> (forall b. Integral b => b -> KeySet -> KeySet)
-> Semigroup KeySet
forall b. Integral b => b -> KeySet -> KeySet
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
$c<> :: KeySet -> KeySet -> KeySet
<> :: KeySet -> KeySet -> KeySet
$csconcat :: NonEmpty KeySet -> KeySet
sconcat :: NonEmpty KeySet -> KeySet
$cstimes :: forall b. Integral b => b -> KeySet -> KeySet
stimes :: forall b. Integral b => b -> KeySet -> KeySet
Semigroup, Semigroup KeySet
KeySet
Semigroup KeySet =>
KeySet
-> (KeySet -> KeySet -> KeySet)
-> ([KeySet] -> KeySet)
-> Monoid KeySet
[KeySet] -> KeySet
KeySet -> KeySet -> KeySet
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
$cmempty :: KeySet
mempty :: KeySet
$cmappend :: KeySet -> KeySet -> KeySet
mappend :: KeySet -> KeySet -> KeySet
$cmconcat :: [KeySet] -> KeySet
mconcat :: [KeySet] -> KeySet
Monoid, KeySet -> ()
(KeySet -> ()) -> NFData KeySet
forall a. (a -> ()) -> NFData a
$crnf :: KeySet -> ()
rnf :: KeySet -> ()
NFData)
instance Show KeySet where
showsPrec :: Int -> KeySet -> ShowS
showsPrec Int
p (KeySet IntSet
is)= Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"fromList " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Key] -> ShowS
forall a. Show a => a -> ShowS
shows [Key]
ks
where ks :: [Key]
ks = [Int] -> [Key]
forall a b. Coercible a b => a -> b
coerce (IntSet -> [Int]
IS.toList IntSet
is) :: [Key]
insertKeySet :: Key -> KeySet -> KeySet
insertKeySet :: Key -> KeySet -> KeySet
insertKeySet = (Int -> IntSet -> IntSet) -> Key -> KeySet -> KeySet
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> IntSet
IS.insert
memberKeySet :: Key -> KeySet -> Bool
memberKeySet :: Key -> KeySet -> Bool
memberKeySet = (Int -> IntSet -> Bool) -> Key -> KeySet -> Bool
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> Bool
IS.member
toListKeySet :: KeySet -> [Key]
toListKeySet :: KeySet -> [Key]
toListKeySet = (IntSet -> [Int]) -> KeySet -> [Key]
forall a b. Coercible a b => a -> b
coerce IntSet -> [Int]
IS.toList
nullKeySet :: KeySet -> Bool
nullKeySet :: KeySet -> Bool
nullKeySet = (IntSet -> Bool) -> KeySet -> Bool
forall a b. Coercible a b => a -> b
coerce IntSet -> Bool
IS.null
differenceKeySet :: KeySet -> KeySet -> KeySet
differenceKeySet :: KeySet -> KeySet -> KeySet
differenceKeySet = (IntSet -> IntSet -> IntSet) -> KeySet -> KeySet -> KeySet
forall a b. Coercible a b => a -> b
coerce IntSet -> IntSet -> IntSet
IS.difference
deleteKeySet :: Key -> KeySet -> KeySet
deleteKeySet :: Key -> KeySet -> KeySet
deleteKeySet = (Int -> IntSet -> IntSet) -> Key -> KeySet -> KeySet
forall a b. Coercible a b => a -> b
coerce Int -> IntSet -> IntSet
IS.delete
fromListKeySet :: [Key] -> KeySet
fromListKeySet :: [Key] -> KeySet
fromListKeySet = ([Int] -> IntSet) -> [Key] -> KeySet
forall a b. Coercible a b => a -> b
coerce [Int] -> IntSet
IS.fromList
singletonKeySet :: Key -> KeySet
singletonKeySet :: Key -> KeySet
singletonKeySet = (Int -> IntSet) -> Key -> KeySet
forall a b. Coercible a b => a -> b
coerce Int -> IntSet
IS.singleton
filterKeySet :: (Key -> Bool) -> KeySet -> KeySet
filterKeySet :: (Key -> Bool) -> KeySet -> KeySet
filterKeySet = ((Int -> Bool) -> IntSet -> IntSet)
-> (Key -> Bool) -> KeySet -> KeySet
forall a b. Coercible a b => a -> b
coerce (Int -> Bool) -> IntSet -> IntSet
IS.filter
lengthKeySet :: KeySet -> Int
lengthKeySet :: KeySet -> Int
lengthKeySet = (IntSet -> Int) -> KeySet -> Int
forall a b. Coercible a b => a -> b
coerce IntSet -> Int
IS.size
newtype KeyMap a = KeyMap (IntMap a)
deriving newtype (KeyMap a -> KeyMap a -> Bool
(KeyMap a -> KeyMap a -> Bool)
-> (KeyMap a -> KeyMap a -> Bool) -> Eq (KeyMap a)
forall a. Eq a => KeyMap a -> KeyMap a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: forall a. Eq a => KeyMap a -> KeyMap a -> Bool
== :: KeyMap a -> KeyMap a -> Bool
$c/= :: forall a. Eq a => KeyMap a -> KeyMap a -> Bool
/= :: KeyMap a -> KeyMap a -> Bool
Eq, Eq (KeyMap a)
Eq (KeyMap a) =>
(KeyMap a -> KeyMap a -> Ordering)
-> (KeyMap a -> KeyMap a -> Bool)
-> (KeyMap a -> KeyMap a -> Bool)
-> (KeyMap a -> KeyMap a -> Bool)
-> (KeyMap a -> KeyMap a -> Bool)
-> (KeyMap a -> KeyMap a -> KeyMap a)
-> (KeyMap a -> KeyMap a -> KeyMap a)
-> Ord (KeyMap a)
KeyMap a -> KeyMap a -> Bool
KeyMap a -> KeyMap a -> Ordering
KeyMap a -> KeyMap a -> KeyMap 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 (KeyMap a)
forall a. Ord a => KeyMap a -> KeyMap a -> Bool
forall a. Ord a => KeyMap a -> KeyMap a -> Ordering
forall a. Ord a => KeyMap a -> KeyMap a -> KeyMap a
$ccompare :: forall a. Ord a => KeyMap a -> KeyMap a -> Ordering
compare :: KeyMap a -> KeyMap a -> Ordering
$c< :: forall a. Ord a => KeyMap a -> KeyMap a -> Bool
< :: KeyMap a -> KeyMap a -> Bool
$c<= :: forall a. Ord a => KeyMap a -> KeyMap a -> Bool
<= :: KeyMap a -> KeyMap a -> Bool
$c> :: forall a. Ord a => KeyMap a -> KeyMap a -> Bool
> :: KeyMap a -> KeyMap a -> Bool
$c>= :: forall a. Ord a => KeyMap a -> KeyMap a -> Bool
>= :: KeyMap a -> KeyMap a -> Bool
$cmax :: forall a. Ord a => KeyMap a -> KeyMap a -> KeyMap a
max :: KeyMap a -> KeyMap a -> KeyMap a
$cmin :: forall a. Ord a => KeyMap a -> KeyMap a -> KeyMap a
min :: KeyMap a -> KeyMap a -> KeyMap a
Ord, NonEmpty (KeyMap a) -> KeyMap a
KeyMap a -> KeyMap a -> KeyMap a
(KeyMap a -> KeyMap a -> KeyMap a)
-> (NonEmpty (KeyMap a) -> KeyMap a)
-> (forall b. Integral b => b -> KeyMap a -> KeyMap a)
-> Semigroup (KeyMap a)
forall b. Integral b => b -> KeyMap a -> KeyMap a
forall a. NonEmpty (KeyMap a) -> KeyMap a
forall a. KeyMap a -> KeyMap a -> KeyMap a
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
forall a b. Integral b => b -> KeyMap a -> KeyMap a
$c<> :: forall a. KeyMap a -> KeyMap a -> KeyMap a
<> :: KeyMap a -> KeyMap a -> KeyMap a
$csconcat :: forall a. NonEmpty (KeyMap a) -> KeyMap a
sconcat :: NonEmpty (KeyMap a) -> KeyMap a
$cstimes :: forall a b. Integral b => b -> KeyMap a -> KeyMap a
stimes :: forall b. Integral b => b -> KeyMap a -> KeyMap a
Semigroup, Semigroup (KeyMap a)
KeyMap a
Semigroup (KeyMap a) =>
KeyMap a
-> (KeyMap a -> KeyMap a -> KeyMap a)
-> ([KeyMap a] -> KeyMap a)
-> Monoid (KeyMap a)
[KeyMap a] -> KeyMap a
KeyMap a -> KeyMap a -> KeyMap a
forall a. Semigroup (KeyMap a)
forall a. KeyMap a
forall a.
Semigroup a =>
a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
forall a. [KeyMap a] -> KeyMap a
forall a. KeyMap a -> KeyMap a -> KeyMap a
$cmempty :: forall a. KeyMap a
mempty :: KeyMap a
$cmappend :: forall a. KeyMap a -> KeyMap a -> KeyMap a
mappend :: KeyMap a -> KeyMap a -> KeyMap a
$cmconcat :: forall a. [KeyMap a] -> KeyMap a
mconcat :: [KeyMap a] -> KeyMap a
Monoid)
instance Show a => Show (KeyMap a) where
showsPrec :: Int -> KeyMap a -> ShowS
showsPrec Int
p (KeyMap IntMap a
im)= Bool -> ShowS -> ShowS
showParen (Int
p Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
10) (ShowS -> ShowS) -> ShowS -> ShowS
forall a b. (a -> b) -> a -> b
$
String -> ShowS
showString String
"fromList " ShowS -> ShowS -> ShowS
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [(Key, a)] -> ShowS
forall a. Show a => a -> ShowS
shows [(Key, a)]
ks
where ks :: [(Key, a)]
ks = [(Int, a)] -> [(Key, a)]
forall a b. Coercible a b => a -> b
coerce (IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
IM.toList IntMap a
im) :: [(Key,a)]
mapKeyMap :: (a -> b) -> KeyMap a -> KeyMap b
mapKeyMap :: forall a b. (a -> b) -> KeyMap a -> KeyMap b
mapKeyMap a -> b
f (KeyMap IntMap a
m) = IntMap b -> KeyMap b
forall a. IntMap a -> KeyMap a
KeyMap ((a -> b) -> IntMap a -> IntMap b
forall a b. (a -> b) -> IntMap a -> IntMap b
IM.map a -> b
f IntMap a
m)
insertKeyMap :: Key -> a -> KeyMap a -> KeyMap a
insertKeyMap :: forall a. Key -> a -> KeyMap a -> KeyMap a
insertKeyMap (UnsafeMkKey Int
k) a
v (KeyMap IntMap a
m) = IntMap a -> KeyMap a
forall a. IntMap a -> KeyMap a
KeyMap (Int -> a -> IntMap a -> IntMap a
forall a. Int -> a -> IntMap a -> IntMap a
IM.insert Int
k a
v IntMap a
m)
lookupKeyMap :: Key -> KeyMap a -> Maybe a
lookupKeyMap :: forall a. Key -> KeyMap a -> Maybe a
lookupKeyMap (UnsafeMkKey Int
k) (KeyMap IntMap a
m) = Int -> IntMap a -> Maybe a
forall a. Int -> IntMap a -> Maybe a
IM.lookup Int
k IntMap a
m
lookupDefaultKeyMap :: a -> Key -> KeyMap a -> a
lookupDefaultKeyMap :: forall a. a -> Key -> KeyMap a -> a
lookupDefaultKeyMap a
a (UnsafeMkKey Int
k) (KeyMap IntMap a
m) = a -> Int -> IntMap a -> a
forall a. a -> Int -> IntMap a -> a
IM.findWithDefault a
a Int
k IntMap a
m
fromListKeyMap :: [(Key,a)] -> KeyMap a
fromListKeyMap :: forall a. [(Key, a)] -> KeyMap a
fromListKeyMap [(Key, a)]
xs = IntMap a -> KeyMap a
forall a. IntMap a -> KeyMap a
KeyMap ([(Int, a)] -> IntMap a
forall a. [(Int, a)] -> IntMap a
IM.fromList ([(Key, a)] -> [(Int, a)]
forall a b. Coercible a b => a -> b
coerce [(Key, a)]
xs))
fromListWithKeyMap :: (a -> a -> a) -> [(Key,a)] -> KeyMap a
fromListWithKeyMap :: forall a. (a -> a -> a) -> [(Key, a)] -> KeyMap a
fromListWithKeyMap a -> a -> a
f [(Key, a)]
xs = IntMap a -> KeyMap a
forall a. IntMap a -> KeyMap a
KeyMap ((a -> a -> a) -> [(Int, a)] -> IntMap a
forall a. (a -> a -> a) -> [(Int, a)] -> IntMap a
IM.fromListWith a -> a -> a
f ([(Key, a)] -> [(Int, a)]
forall a b. Coercible a b => a -> b
coerce [(Key, a)]
xs))
toListKeyMap :: KeyMap a -> [(Key,a)]
toListKeyMap :: forall a. KeyMap a -> [(Key, a)]
toListKeyMap (KeyMap IntMap a
m) = [(Int, a)] -> [(Key, a)]
forall a b. Coercible a b => a -> b
coerce (IntMap a -> [(Int, a)]
forall a. IntMap a -> [(Int, a)]
IM.toList IntMap a
m)
elemsKeyMap :: KeyMap a -> [a]
elemsKeyMap :: forall a. KeyMap a -> [a]
elemsKeyMap (KeyMap IntMap a
m) = IntMap a -> [a]
forall a. IntMap a -> [a]
IM.elems IntMap a
m
restrictKeysKeyMap :: KeyMap a -> KeySet -> KeyMap a
restrictKeysKeyMap :: forall a. KeyMap a -> KeySet -> KeyMap a
restrictKeysKeyMap (KeyMap IntMap a
m) (KeySet IntSet
s) = IntMap a -> KeyMap a
forall a. IntMap a -> KeyMap a
KeyMap (IntMap a -> IntSet -> IntMap a
forall a. IntMap a -> IntSet -> IntMap a
IM.restrictKeys IntMap a
m IntSet
s)