{-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeApplications #-} {-# LANGUAGE ViewPatterns #-} -- | -- Module : Data.EnumMap.Strict -- Description : Data.IntMap.Strict, wrapped with Enum module Data.EnumMap.Strict ( -- * Map type EnumMap (..), -- * Construction empty, singleton, fromSet, -- ** From Unordered Lists fromList, fromListWith, fromListWithKey, -- ** From Ascending Lists fromAscList, fromAscListWith, fromAscListWithKey, fromDistinctAscList, -- * Insertion insert, insertWith, insertWithKey, insertLookupWithKey, -- * Deletion\/Update delete, adjust, adjustWithKey, update, updateWithKey, updateLookupWithKey, alter, alterF, -- * Query -- ** Lookup lookup, (!?), (!), findWithDefault, member, notMember, lookupLT, lookupGT, lookupLE, lookupGE, -- ** Size null, size, -- * Combine -- ** Union union, unionWith, unionWithKey, unions, unionsWith, -- ** Difference difference, (\\), differenceWith, differenceWithKey, -- ** Intersection intersection, intersectionWith, intersectionWithKey, -- ** Disjoint disjoint, -- ** Universal combining function mergeWithKey, -- * Traversal -- ** Map map, mapWithKey, traverseWithKey, mapAccum, mapAccumWithKey, mapAccumRWithKey, mapKeys, mapKeysWith, mapKeysMonotonic, -- * Folds foldr, foldl, foldrWithKey, foldlWithKey, foldMapWithKey, -- ** Strict folds foldr', foldl', foldrWithKey', foldlWithKey', -- * Conversion elems, keys, assocs, keysSet, -- ** Lists toList, -- ** Ordered lists toAscList, toDescList, -- * Filter filter, filterWithKey, restrictKeys, withoutKeys, partition, partitionWithKey, mapMaybe, mapMaybeWithKey, mapEither, mapEitherWithKey, split, splitLookup, splitRoot, -- * Submap isSubmapOf, isSubmapOfBy, isProperSubmapOf, isProperSubmapOfBy, -- * Min\/Max lookupMin, lookupMax, findMin, findMax, deleteMin, deleteMax, deleteFindMin, deleteFindMax, updateMin, updateMax, updateMinWithKey, updateMaxWithKey, minView, maxView, minViewWithKey, maxViewWithKey, ) where import Data.Bifunctor (first) import Data.Coerce (Coercible, coerce) import Data.EnumMap.Wrapper (EnumMap (..)) import Data.EnumSet.Wrapper (EnumSet (..)) import qualified Data.IntMap.Strict as IntMap import Prelude ( ($), (.), Applicative, Bool, Either, Enum, Eq, Foldable, Functor, Int, Maybe, Monoid, fmap, fromEnum, toEnum, ) (!) :: Enum k => EnumMap k a -> k -> a (!) (coerce -> m) (fromEnum -> k) = (IntMap.!) m k {-# INLINE (!) #-} (!?) :: Enum k => EnumMap k a -> k -> Maybe a (!?) (coerce -> m) (fromEnum -> k) = (IntMap.!?) m k {-# INLINE (!?) #-} (\\) :: forall k a b. EnumMap k a -> EnumMap k b -> EnumMap k a (\\) = coerce $ (IntMap.\\) @a @b {-# INLINE (\\) #-} infixl 9 !?, \\ null :: forall k a. EnumMap k a -> Bool null = coerce $ IntMap.null @a {-# INLINE null #-} size :: forall k a. EnumMap k a -> Int size = coerce $ IntMap.size @a {-# INLINE size #-} member :: forall k a. Enum k => k -> EnumMap k a -> Bool member (fromEnum -> k) = coerce $ IntMap.member @a k {-# INLINE member #-} notMember :: forall k a. Enum k => k -> EnumMap k a -> Bool notMember (fromEnum -> k) = coerce $ IntMap.notMember @a k {-# INLINE notMember #-} lookup :: forall k a. Enum k => k -> EnumMap k a -> Maybe a lookup (fromEnum -> k) = coerce $ IntMap.lookup @a k {-# INLINE lookup #-} findWithDefault :: Enum k => a -> k -> EnumMap k a -> a findWithDefault def (fromEnum -> k) = coerce $ IntMap.findWithDefault def k {-# INLINE findWithDefault #-} lookupLT :: forall k a. Enum k => k -> EnumMap k a -> Maybe (k, a) lookupLT (fromEnum -> k) = fmap (first toEnum) . coerce (IntMap.lookupLT @a k) {-# INLINE lookupLT #-} lookupGT :: forall k a. Enum k => k -> EnumMap k a -> Maybe (k, a) lookupGT (fromEnum -> k) = fmap (first toEnum) . coerce (IntMap.lookupGT @a k) {-# INLINE lookupGT #-} lookupLE :: forall k a. Enum k => k -> EnumMap k a -> Maybe (k, a) lookupLE (fromEnum -> k) = fmap (first toEnum) . coerce (IntMap.lookupLE @a k) {-# INLINE lookupLE #-} lookupGE :: forall k a. Enum k => k -> EnumMap k a -> Maybe (k, a) lookupGE (fromEnum -> k) = fmap (first toEnum) . coerce (IntMap.lookupGE @a k) {-# INLINE lookupGE #-} disjoint :: forall k a b. EnumMap k a -> EnumMap k b -> Bool disjoint = coerce $ IntMap.disjoint @a @b {-# INLINE disjoint #-} empty :: forall k a. EnumMap k a empty = coerce $ IntMap.empty @a {-# INLINE empty #-} singleton :: forall k a. Enum k => k -> a -> EnumMap k a singleton (fromEnum -> k) = coerce $ IntMap.singleton @a k {-# INLINE singleton #-} insert :: forall k a. Enum k => k -> a -> EnumMap k a -> EnumMap k a insert (fromEnum -> k) = coerce $ IntMap.insert @a k {-# INLINE insert #-} insertWith :: Enum k => (a -> a -> a) -> k -> a -> EnumMap k a -> EnumMap k a insertWith f (fromEnum -> k) = coerce $ IntMap.insertWith f k {-# INLINE insertWith #-} insertWithKey :: Enum k => (k -> a -> a -> a) -> k -> a -> EnumMap k a -> EnumMap k a insertWithKey ((. toEnum) -> f) (fromEnum -> k) = coerce $ IntMap.insertWithKey f k {-# INLINE insertWithKey #-} insertLookupWithKey :: Enum k => (k -> a -> a -> a) -> k -> a -> EnumMap k a -> (Maybe a, EnumMap k a) insertLookupWithKey ((. toEnum) -> f) (fromEnum -> k) = coerce $ IntMap.insertLookupWithKey f k {-# INLINE insertLookupWithKey #-} delete :: forall k a. Enum k => k -> EnumMap k a -> EnumMap k a delete (fromEnum -> k) = coerce $ IntMap.delete @a k {-# INLINE delete #-} adjust :: Enum k => (a -> a) -> k -> EnumMap k a -> EnumMap k a adjust f (fromEnum -> k) = coerce $ IntMap.adjust f k {-# INLINE adjust #-} adjustWithKey :: Enum k => (k -> a -> a) -> k -> EnumMap k a -> EnumMap k a adjustWithKey ((. toEnum) -> f) (fromEnum -> k) = coerce $ IntMap.adjustWithKey f k {-# INLINE adjustWithKey #-} update :: Enum k => (a -> Maybe a) -> k -> EnumMap k a -> EnumMap k a update f (fromEnum -> k) = coerce $ IntMap.update f k {-# INLINE update #-} updateWithKey :: Enum k => (k -> a -> Maybe a) -> k -> EnumMap k a -> EnumMap k a updateWithKey ((. toEnum) -> f) (fromEnum -> k) = coerce $ IntMap.updateWithKey f k {-# INLINE updateWithKey #-} updateLookupWithKey :: Enum k => (k -> a -> Maybe a) -> k -> EnumMap k a -> (Maybe a, EnumMap k a) updateLookupWithKey ((. toEnum) -> f) (fromEnum -> k) = coerce $ IntMap.updateLookupWithKey f k {-# INLINE updateLookupWithKey #-} alter :: Enum k => (Maybe a -> Maybe a) -> k -> EnumMap k a -> EnumMap k a alter f (fromEnum -> k) = coerce $ IntMap.alter f k {-# INLINE alter #-} alterF :: (Enum k, Functor f, Coercible (f (IntMap.IntMap a)) (f (EnumMap k a))) => (Maybe a -> f (Maybe a)) -> k -> EnumMap k a -> f (EnumMap k a) alterF f (fromEnum -> k) = coerce $ IntMap.alterF f k {-# INLINE alterF #-} unions :: forall f k a. (Foldable f, Coercible (f (IntMap.IntMap a)) (f (EnumMap k a))) => f (EnumMap k a) -> EnumMap k a unions = coerce $ IntMap.unions @f @a {-# INLINE unions #-} unionsWith :: forall f k a. (Foldable f, Coercible (f (IntMap.IntMap a)) (f (EnumMap k a))) => (a -> a -> a) -> f (EnumMap k a) -> EnumMap k a unionsWith = coerce $ IntMap.unionsWith @f @a {-# INLINE unionsWith #-} union :: forall k a. EnumMap k a -> EnumMap k a -> EnumMap k a union = coerce $ IntMap.union @a {-# INLINE union #-} unionWith :: forall k a. (a -> a -> a) -> EnumMap k a -> EnumMap k a -> EnumMap k a unionWith = coerce $ IntMap.unionWith @a {-# INLINE unionWith #-} unionWithKey :: Enum k => (k -> a -> a -> a) -> EnumMap k a -> EnumMap k a -> EnumMap k a unionWithKey ((. toEnum) -> f) = coerce $ IntMap.unionWithKey f {-# INLINE unionWithKey #-} difference :: forall k a b. EnumMap k a -> EnumMap k b -> EnumMap k a difference = coerce $ IntMap.difference @a @b {-# INLINE difference #-} differenceWith :: forall k a b. (a -> b -> Maybe a) -> EnumMap k a -> EnumMap k b -> EnumMap k a differenceWith = coerce $ IntMap.differenceWith @a @b {-# INLINE differenceWith #-} differenceWithKey :: Enum k => (k -> a -> b -> Maybe a) -> EnumMap k a -> EnumMap k b -> EnumMap k a differenceWithKey ((. toEnum) -> f) = coerce $ IntMap.differenceWithKey f {-# INLINE differenceWithKey #-} withoutKeys :: forall k a. EnumMap k a -> EnumSet k -> EnumMap k a withoutKeys = coerce $ IntMap.withoutKeys @a {-# INLINE withoutKeys #-} intersection :: forall k a b. EnumMap k a -> EnumMap k b -> EnumMap k a intersection = coerce $ IntMap.intersection @a @b {-# INLINE intersection #-} restrictKeys :: forall k a. EnumMap k a -> EnumSet k -> EnumMap k a restrictKeys = coerce $ IntMap.restrictKeys @a {-# INLINE restrictKeys #-} intersectionWith :: forall k a b c. (a -> b -> c) -> EnumMap k a -> EnumMap k b -> EnumMap k c intersectionWith = coerce $ IntMap.intersectionWith @a @b @c {-# INLINE intersectionWith #-} intersectionWithKey :: Enum k => (k -> a -> b -> c) -> EnumMap k a -> EnumMap k b -> EnumMap k c intersectionWithKey ((. toEnum) -> f) = coerce $ IntMap.intersectionWithKey f {-# INLINE intersectionWithKey #-} mergeWithKey :: Enum k => (k -> a -> b -> Maybe c) -> (EnumMap k a -> EnumMap k c) -> (EnumMap k b -> EnumMap k c) -> EnumMap k a -> EnumMap k b -> EnumMap k c mergeWithKey ((. toEnum) -> f) = coerce $ IntMap.mergeWithKey f {-# INLINE mergeWithKey #-} updateMinWithKey :: Enum k => (k -> a -> Maybe a) -> EnumMap k a -> EnumMap k a updateMinWithKey ((. toEnum) -> f) = coerce $ IntMap.updateMinWithKey f {-# INLINE updateMinWithKey #-} updateMaxWithKey :: Enum k => (k -> a -> Maybe a) -> EnumMap k a -> EnumMap k a updateMaxWithKey ((. toEnum) -> f) = coerce $ IntMap.updateMaxWithKey f {-# INLINE updateMaxWithKey #-} maxViewWithKey :: forall k a. Enum k => EnumMap k a -> Maybe ((k, a), EnumMap k a) maxViewWithKey = fmap (first (first toEnum)) . coerce (IntMap.maxViewWithKey @a) {-# INLINE maxViewWithKey #-} minViewWithKey :: forall k a. Enum k => EnumMap k a -> Maybe ((k, a), EnumMap k a) minViewWithKey = fmap (first (first toEnum)) . coerce (IntMap.minViewWithKey @a) {-# INLINE minViewWithKey #-} updateMax :: forall k a. (a -> Maybe a) -> EnumMap k a -> EnumMap k a updateMax = coerce $ IntMap.updateMax @a {-# INLINE updateMax #-} updateMin :: forall k a. (a -> Maybe a) -> EnumMap k a -> EnumMap k a updateMin = coerce $ IntMap.updateMin @a {-# INLINE updateMin #-} maxView :: forall k a. EnumMap k a -> Maybe (a, EnumMap k a) maxView = coerce $ IntMap.maxView @a {-# INLINE maxView #-} minView :: forall k a. EnumMap k a -> Maybe (a, EnumMap k a) minView = coerce $ IntMap.minView @a {-# INLINE minView #-} deleteFindMax :: forall k a. Enum k => EnumMap k a -> ((k, a), EnumMap k a) deleteFindMax = first (first toEnum) . coerce (IntMap.deleteFindMax @a) {-# INLINE deleteFindMax #-} deleteFindMin :: forall k a. Enum k => EnumMap k a -> ((k, a), EnumMap k a) deleteFindMin = first (first toEnum) . coerce (IntMap.deleteFindMin @a) {-# INLINE deleteFindMin #-} lookupMin :: forall k a. Enum k => EnumMap k a -> Maybe (k, a) lookupMin = fmap (first toEnum) . coerce (IntMap.lookupMin @a) {-# INLINE lookupMin #-} findMin :: forall k a. Enum k => EnumMap k a -> (k, a) findMin = first toEnum . coerce (IntMap.findMin @a) {-# INLINE findMin #-} lookupMax :: forall k a. Enum k => EnumMap k a -> Maybe (k, a) lookupMax = fmap (first toEnum) . coerce (IntMap.lookupMax @a) {-# INLINE lookupMax #-} findMax :: forall k a. Enum k => EnumMap k a -> (k, a) findMax = first toEnum . coerce (IntMap.findMax @a) {-# INLINE findMax #-} deleteMin :: forall k a. EnumMap k a -> EnumMap k a deleteMin = coerce $ IntMap.deleteMin @a {-# INLINE deleteMin #-} deleteMax :: forall k a. EnumMap k a -> EnumMap k a deleteMax = coerce $ IntMap.deleteMax @a {-# INLINE deleteMax #-} isProperSubmapOf :: forall k a. Eq a => EnumMap k a -> EnumMap k a -> Bool isProperSubmapOf = coerce $ IntMap.isProperSubmapOf @a {-# INLINE isProperSubmapOf #-} isProperSubmapOfBy :: forall k a b. (a -> b -> Bool) -> EnumMap k a -> EnumMap k b -> Bool isProperSubmapOfBy = coerce $ IntMap.isProperSubmapOfBy @a @b {-# INLINE isProperSubmapOfBy #-} isSubmapOf :: forall k a. Eq a => EnumMap k a -> EnumMap k a -> Bool isSubmapOf = coerce $ IntMap.isSubmapOf @a {-# INLINE isSubmapOf #-} isSubmapOfBy :: forall k a b. (a -> b -> Bool) -> EnumMap k a -> EnumMap k b -> Bool isSubmapOfBy = coerce $ IntMap.isSubmapOfBy @a @b {-# INLINE isSubmapOfBy #-} map :: forall k a b. (a -> b) -> EnumMap k a -> EnumMap k b map = coerce $ IntMap.map @a @b {-# INLINE map #-} mapWithKey :: Enum k => (k -> a -> b) -> EnumMap k a -> EnumMap k b mapWithKey ((. toEnum) -> f) = coerce $ IntMap.mapWithKey f {-# INLINE mapWithKey #-} traverseWithKey :: (Enum k, Applicative t, Coercible (t (IntMap.IntMap a)) (t (EnumMap k a)), Coercible (t (IntMap.IntMap b)) (t (EnumMap k b))) => (k -> a -> t b) -> EnumMap k a -> t (EnumMap k b) traverseWithKey ((. toEnum) -> f) = coerce $ IntMap.traverseWithKey f {-# INLINE traverseWithKey #-} mapAccum :: forall k a b c. (a -> b -> (a, c)) -> a -> EnumMap k b -> (a, EnumMap k c) mapAccum = coerce $ IntMap.mapAccum @a @b @c {-# INLINE mapAccum #-} mapAccumWithKey :: Enum k => (a -> k -> b -> (a, c)) -> a -> EnumMap k b -> (a, EnumMap k c) mapAccumWithKey (fmap (. toEnum) -> f) = coerce $ IntMap.mapAccumWithKey f {-# INLINE mapAccumWithKey #-} mapAccumRWithKey :: Enum k => (a -> k -> b -> (a, c)) -> a -> EnumMap k b -> (a, EnumMap k c) mapAccumRWithKey (fmap (. toEnum) -> f) = coerce $ IntMap.mapAccumRWithKey f {-# INLINE mapAccumRWithKey #-} mapKeys :: forall k a. Enum k => (k -> k) -> EnumMap k a -> EnumMap k a mapKeys ((. toEnum) . (fromEnum .) -> f) = coerce $ IntMap.mapKeys @a f {-# INLINE mapKeys #-} mapKeysWith :: Enum k => (a -> a -> a) -> (k -> k) -> EnumMap k a -> EnumMap k a mapKeysWith c ((. toEnum) . (fromEnum .) -> f) = coerce $ IntMap.mapKeysWith c f {-# INLINE mapKeysWith #-} mapKeysMonotonic :: forall k a. Enum k => (k -> k) -> EnumMap k a -> EnumMap k a mapKeysMonotonic ((. toEnum) . (fromEnum .) -> f) = coerce $ IntMap.mapKeysMonotonic @a f {-# INLINE mapKeysMonotonic #-} filter :: forall k a. (a -> Bool) -> EnumMap k a -> EnumMap k a filter = coerce $ IntMap.filter @a {-# INLINE filter #-} filterWithKey :: Enum k => (k -> a -> Bool) -> EnumMap k a -> EnumMap k a filterWithKey ((. toEnum) -> f) = coerce $ IntMap.filterWithKey f {-# INLINE filterWithKey #-} partition :: forall k a. (a -> Bool) -> EnumMap k a -> (EnumMap k a, EnumMap k a) partition = coerce $ IntMap.partition @a {-# INLINE partition #-} partitionWithKey :: Enum k => (k -> a -> Bool) -> EnumMap k a -> (EnumMap k a, EnumMap k a) partitionWithKey ((. toEnum) -> f) = coerce $ IntMap.partitionWithKey f {-# INLINE partitionWithKey #-} mapMaybe :: forall k a b. (a -> Maybe b) -> EnumMap k a -> EnumMap k b mapMaybe = coerce $ IntMap.mapMaybe @a @b {-# INLINE mapMaybe #-} mapMaybeWithKey :: Enum k => (k -> a -> Maybe b) -> EnumMap k a -> EnumMap k b mapMaybeWithKey ((. toEnum) -> f) = coerce $ IntMap.mapMaybeWithKey f {-# INLINE mapMaybeWithKey #-} mapEither :: forall k a b c. (a -> Either b c) -> EnumMap k a -> (EnumMap k b, EnumMap k c) mapEither = coerce $ IntMap.mapEither @a @b @c {-# INLINE mapEither #-} mapEitherWithKey :: Enum k => (k -> a -> Either b c) -> EnumMap k a -> (EnumMap k b, EnumMap k c) mapEitherWithKey ((. toEnum) -> f) = coerce $ IntMap.mapEitherWithKey f {-# INLINE mapEitherWithKey #-} split :: forall k a. Enum k => k -> EnumMap k a -> (EnumMap k a, EnumMap k a) split (fromEnum -> k) = coerce $ IntMap.split @a k {-# INLINE split #-} splitLookup :: forall k a. Enum k => k -> EnumMap k a -> (EnumMap k a, Maybe a, EnumMap k a) splitLookup (fromEnum -> k) = coerce $ IntMap.splitLookup @a k {-# INLINE splitLookup #-} foldr :: forall k a b. (a -> b -> b) -> b -> EnumMap k a -> b foldr = coerce $ IntMap.foldr @a @b {-# INLINE foldr #-} foldr' :: forall k a b. (a -> b -> b) -> b -> EnumMap k a -> b foldr' = coerce $ IntMap.foldr' @a @b {-# INLINE foldr' #-} foldl :: forall k a b. (a -> b -> a) -> a -> EnumMap k b -> a foldl = coerce $ IntMap.foldl @a @b {-# INLINE foldl #-} foldl' :: forall k a b. (a -> b -> a) -> a -> EnumMap k b -> a foldl' = coerce $ IntMap.foldl' @a @b {-# INLINE foldl' #-} foldrWithKey :: Enum k => (k -> a -> b -> b) -> b -> EnumMap k a -> b foldrWithKey ((. toEnum) -> f) = coerce $ IntMap.foldrWithKey f {-# INLINE foldrWithKey #-} foldrWithKey' :: Enum k => (k -> a -> b -> b) -> b -> EnumMap k a -> b foldrWithKey' ((. toEnum) -> f) = coerce $ IntMap.foldrWithKey' f {-# INLINE foldrWithKey' #-} foldlWithKey :: Enum k => (a -> k -> b -> a) -> a -> EnumMap k b -> a foldlWithKey (fmap (. toEnum) -> f) = coerce $ IntMap.foldlWithKey f {-# INLINE foldlWithKey #-} foldlWithKey' :: Enum k => (a -> k -> b -> a) -> a -> EnumMap k b -> a foldlWithKey' (fmap (. toEnum) -> f) = coerce $ IntMap.foldlWithKey' f {-# INLINE foldlWithKey' #-} foldMapWithKey :: (Enum k, Monoid m) => (k -> a -> m) -> EnumMap k a -> m foldMapWithKey ((. toEnum) -> f) = coerce $ IntMap.foldMapWithKey f {-# INLINE foldMapWithKey #-} elems :: forall k a. EnumMap k a -> [a] elems = coerce $ IntMap.elems @a {-# INLINE elems #-} keys :: forall k a. Enum k => EnumMap k a -> [k] keys = fmap toEnum . coerce (IntMap.keys @a) {-# INLINE keys #-} assocs :: forall k a. Enum k => EnumMap k a -> [(k, a)] assocs = fmap (first toEnum) . coerce (IntMap.assocs @a) {-# INLINE assocs #-} keysSet :: forall k a. EnumMap k a -> EnumSet k keysSet = coerce $ IntMap.keysSet @a {-# INLINE keysSet #-} fromSet :: Enum k => (k -> a) -> EnumSet k -> EnumMap k a fromSet ((. toEnum) -> f) = coerce $ IntMap.fromSet f {-# INLINE fromSet #-} toList :: forall k a. Enum k => EnumMap k a -> [(k, a)] toList = fmap (first toEnum) . coerce (IntMap.toList @a) {-# INLINE toList #-} toAscList :: forall k a. Enum k => EnumMap k a -> [(k, a)] toAscList = fmap (first toEnum) . coerce (IntMap.toAscList @a) {-# INLINE toAscList #-} toDescList :: forall k a. Enum k => EnumMap k a -> [(k, a)] toDescList = fmap (first toEnum) . coerce (IntMap.toDescList @a) {-# INLINE toDescList #-} fromList :: Enum k => [(k, a)] -> EnumMap k a fromList (fmap (first fromEnum) -> xs) = coerce $ IntMap.fromList xs {-# INLINE fromList #-} fromListWith :: Enum k => (a -> a -> a) -> [(k, a)] -> EnumMap k a fromListWith f (fmap (first fromEnum) -> xs) = coerce $ IntMap.fromListWith f xs {-# INLINE fromListWith #-} fromListWithKey :: Enum k => (k -> a -> a -> a) -> [(k, a)] -> EnumMap k a fromListWithKey ((. toEnum) -> f) (fmap (first fromEnum) -> xs) = coerce $ IntMap.fromListWithKey f xs {-# INLINE fromListWithKey #-} fromAscList :: Enum k => [(k, a)] -> EnumMap k a fromAscList (fmap (first fromEnum) -> xs) = coerce $ IntMap.fromAscList xs {-# INLINE fromAscList #-} fromAscListWith :: Enum k => (a -> a -> a) -> [(k, a)] -> EnumMap k a fromAscListWith f (fmap (first fromEnum) -> xs) = coerce $ IntMap.fromAscListWith f xs {-# INLINE fromAscListWith #-} fromAscListWithKey :: Enum k => (k -> a -> a -> a) -> [(k, a)] -> EnumMap k a fromAscListWithKey ((. toEnum) -> f) (fmap (first fromEnum) -> xs) = coerce $ IntMap.fromAscListWithKey f xs {-# INLINE fromAscListWithKey #-} fromDistinctAscList :: Enum k => [(k, a)] -> EnumMap k a fromDistinctAscList (fmap (first fromEnum) -> xs) = coerce $ IntMap.fromDistinctAscList xs {-# INLINE fromDistinctAscList #-} splitRoot :: forall k a. EnumMap k a -> [EnumMap k a] splitRoot = coerce $ IntMap.splitRoot @a {-# INLINE splitRoot #-}