module Data.Map.Ordered
( OSMap, Map, empty, lookup, insert, delete, fromList, fromListWith, toList, map, mapMaybe
, lookupLT, lookupGT, lookupLE, lookupGE, lookupM, elemAt
, singleton, insertWith
, member, elems, unionWith, difference, union, findWithDefault, size, null, isSubmapOf, unions
, intersection, foldrWithKey, foldlWithKey, filter, filterWithKey
, keys, toDescList, updateLookupWithKey
, deleteLookup, insertLookupWithKey, adjust, assocs, insertWith'
, alter, differenceWith, updateWithKey, update, mapKeys, insertWithKey, insertWithKey'
, keysSet
, maxView, maxViewWithKey, minView, minViewWithKey
, intersectionWith, fromDistinctAscList
, toDataMap, fromDataMap, hasKey, hasValue
)
where
import Control.Arrow (second)
import Control.DeepSeq (NFData(..))
import Data.Coerce
import Data.Data
import Data.Hashable
import Data.List (foldl')
import Data.Maybe (isJust)
import Prelude hiding (map, lookup, null, filter)
import Test.QuickCheck
import qualified Data.Map.Strict as DM
import qualified Data.Set as Set
type Map = OSMap
newtype OSMap k v = OSMap { unOSMap :: DM.Map k v }
deriving (Eq, Ord, Read, Show, Foldable, NFData, Data)
instance (Hashable k, Hashable v) => Hashable (OSMap k v) where
hashWithSalt = foldlWithKey updateHash
where
updateHash salt k v = hashWithSalt salt k `hashWithSalt` v
instance Functor (OSMap k) where
fmap = map
instance (Ord k, Arbitrary k, Arbitrary v) => Arbitrary (OSMap k v) where
arbitrary = OSMap <$> arbitrary
shrink = coerce . shrink . unOSMap
instance Traversable (OSMap k) where
traverse f (OSMap m) =
fromDataMap <$> DM.traverseWithKey (\_ x -> let y = f x in y) m
instance (Ord k) => Monoid (OSMap k v) where
mempty = empty
mconcat = unions
mappend = union
fromDataMap :: DM.Map k v -> OSMap k v
fromDataMap dm = DM.foldr (\a b -> a `seq` b) () dm `seq` OSMap dm
toDataMap :: OSMap k v -> DM.Map k v
toDataMap = unOSMap
empty :: OSMap k v
empty = OSMap DM.empty
member :: (Ord k) => k -> OSMap k v -> Bool
member k (OSMap m) = DM.member k m
lookup :: (Ord k) => k -> OSMap k v -> Maybe v
lookup k (OSMap hm) = DM.lookup k hm
lookupM :: (Show k, Ord k, Monad m) => k -> OSMap k v -> m v
lookupM k (OSMap hm) =
case DM.lookup k hm of
Nothing -> fail ("Could not find " ++ show k ++ " in Map.")
Just x -> pure x
lookupLT :: (Ord k) => k -> OSMap k v -> Maybe (k, v)
lookupLT k (OSMap hm) = DM.lookupLT k hm
lookupGT :: (Ord k) => k -> OSMap k v -> Maybe (k, v)
lookupGT k (OSMap hm) = DM.lookupGT k hm
lookupLE :: (Ord k) => k -> OSMap k v -> Maybe (k, v)
lookupLE k (OSMap hm) = DM.lookupLE k hm
lookupGE :: (Ord k) => k -> OSMap k v -> Maybe (k, v)
lookupGE k (OSMap hm) = DM.lookupGE k hm
insert :: (Ord k) => k -> v -> OSMap k v -> OSMap k v
insert k v (OSMap hm) = OSMap (DM.insert k v hm)
delete :: (Ord k) => k -> OSMap k v -> OSMap k v
delete k (OSMap hm) = OSMap (DM.delete k hm)
fromList :: (Ord k) => [(k,v)] -> OSMap k v
fromList = OSMap . DM.fromList
fromListWith :: (Ord k) => (v -> v -> v) -> [(k,v)] -> OSMap k v
fromListWith f kvs = OSMap $ DM.fromListWith f kvs
toList :: OSMap k v -> [(k, v)]
toList (OSMap hm) = DM.toList hm
toDescList :: OSMap k v -> [(k, v)]
toDescList (OSMap hm) = DM.toDescList hm
map :: (v -> v') -> OSMap k v -> OSMap k v'
map f (OSMap m) = OSMap (DM.map f m)
mapMaybe :: (v -> Maybe v') -> OSMap k v -> OSMap k v'
mapMaybe f (OSMap m) = OSMap (DM.mapMaybe f m)
singleton :: k -> v -> OSMap k v
singleton k v = OSMap (DM.singleton k v)
insertWith :: (Ord k) => (v -> v -> v) -> k -> v -> OSMap k v -> OSMap k v
insertWith f k !v (OSMap hm) = OSMap (DM.insertWith f k v hm)
elems :: OSMap k v -> [v]
elems = DM.elems . unOSMap
keys :: OSMap k v -> [k]
keys = DM.keys . unOSMap
keysSet :: OSMap k v -> Set.Set k
keysSet = DM.keysSet . unOSMap
union :: Ord k => OSMap k v -> OSMap k v -> OSMap k v
union (OSMap m1) (OSMap m2) = OSMap (DM.union m1 m2)
unions :: Ord k => [OSMap k v] -> OSMap k v
unions ts = foldl' union empty ts
unionWith :: Ord k => (v -> v -> v) -> OSMap k v -> OSMap k v -> OSMap k v
unionWith f (OSMap m1) (OSMap m2) = OSMap (DM.unionWith f m1 m2)
difference :: (Ord k) => OSMap k v -> OSMap k w -> OSMap k v
difference (OSMap m1) (OSMap m2) = OSMap (DM.difference m1 m2)
intersection :: (Ord k) => OSMap k v -> OSMap k w -> OSMap k v
intersection (OSMap m1) (OSMap m2) = OSMap (DM.intersection m1 m2)
findWithDefault :: (Ord k) => a -> k -> OSMap k a -> a
findWithDefault def k (OSMap m) = DM.findWithDefault def k m
elemAt :: Int -> OSMap k a -> (k, a)
elemAt n (OSMap m) = DM.elemAt n m
size :: OSMap k v -> Int
size = DM.size . unOSMap
null :: OSMap k v -> Bool
null = DM.null . unOSMap
isSubmapOf :: (Ord k, Eq a) => OSMap k a -> OSMap k a -> Bool
isSubmapOf (OSMap a) (OSMap b) = DM.isSubmapOf a b
foldrWithKey :: (k -> v -> a -> a) -> a -> OSMap k v -> a
foldrWithKey f a (OSMap hm) = DM.foldrWithKey f a hm
foldlWithKey :: (a -> k -> v -> a) -> a -> OSMap k v -> a
foldlWithKey f a (OSMap hm) = DM.foldlWithKey f a hm
filter :: (v -> Bool) -> OSMap k v -> OSMap k v
filter f (OSMap m) = OSMap (DM.filter f m)
filterWithKey :: (k -> v -> Bool) -> OSMap k v -> OSMap k v
filterWithKey f (OSMap m) = OSMap (DM.filterWithKey f m)
updateLookupWithKey :: Ord k => (k -> a -> Maybe a) -> k -> OSMap k a -> (Maybe a, OSMap k a)
updateLookupWithKey f k (OSMap curMap) =
let (mv, newMap) = DM.updateLookupWithKey f k curMap
in (mv, OSMap newMap)
deleteLookup :: Ord k => k -> OSMap k v -> (Maybe v, OSMap k v)
deleteLookup = updateLookupWithKey (\_k _v -> Nothing)
insertLookupWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> OSMap k a -> (Maybe a, OSMap k a)
insertLookupWithKey f k !newV (OSMap curM) =
let (mOldV, newM) = DM.insertLookupWithKey f k newV curM
in (mOldV, OSMap newM)
adjust :: Ord k => (a -> a) -> k -> Map k a -> Map k a
adjust f k = OSMap . DM.adjust f k . unOSMap
assocs :: OSMap k a -> [(k, a)]
assocs = DM.assocs . unOSMap
insertWith' :: Ord k => (a -> a -> a) -> k -> a -> OSMap k a -> OSMap k a
insertWith' f k !v (OSMap dm) = OSMap (DM.insertWith f k v dm)
alter :: Ord k => (Maybe a -> Maybe a) -> k -> OSMap k a -> OSMap k a
alter f k (OSMap dm) = OSMap (DM.alter f k dm)
differenceWith :: Ord k => (a -> b -> Maybe a) -> OSMap k a -> OSMap k b -> OSMap k a
differenceWith f (OSMap dmA) (OSMap dmB) = OSMap (DM.differenceWith f dmA dmB)
updateWithKey :: Ord k => (k -> a -> Maybe a) -> k -> OSMap k a -> OSMap k a
updateWithKey f k (OSMap dm) = OSMap (DM.updateWithKey f k dm)
update :: Ord k => (a -> Maybe a) -> k -> OSMap k a -> OSMap k a
update f k (OSMap dm) = OSMap (DM.update f k dm)
insertWithKey :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithKey f k !v (OSMap dm) = OSMap (DM.insertWithKey f k v dm)
insertWithKey' :: Ord k => (k -> a -> a -> a) -> k -> a -> Map k a -> Map k a
insertWithKey' = insertWithKey
mapKeys :: Ord k2 => (k1 -> k2) -> OSMap k1 a -> OSMap k2 a
mapKeys f (OSMap dm) = OSMap (DM.mapKeys f dm)
maxView :: OSMap k a -> Maybe (a, OSMap k a)
maxView (OSMap m) = fmap (second OSMap) (DM.maxView m)
maxViewWithKey :: OSMap k a -> Maybe ((k, a), OSMap k a)
maxViewWithKey (OSMap m) = fmap (second OSMap) (DM.maxViewWithKey m)
minView :: OSMap k a -> Maybe (a, OSMap k a)
minView (OSMap m) = fmap (second OSMap) (DM.minView m)
minViewWithKey :: OSMap k a -> Maybe ((k, a), OSMap k a)
minViewWithKey = fmap (second OSMap) . DM.minViewWithKey . unOSMap
intersectionWith :: Ord k => (a -> b -> c) -> OSMap k a -> OSMap k b -> OSMap k c
intersectionWith f (OSMap l) (OSMap r) =
OSMap (DM.intersectionWith f l r)
fromDistinctAscList :: [(k,v)] -> OSMap k v
fromDistinctAscList = OSMap . DM.fromDistinctAscList
hasValue :: Int -> OSMap Int Int -> Bool
hasValue v m = any (\(_, x) -> x == v) (toList m)
hasKey :: Int -> OSMap Int Int -> Bool
hasKey k m = isJust (lookup k m)