{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveTraversable #-}
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeFamilies #-}
module Dhall.Map
(
Map
, singleton
, fromList
, sort
, isSorted
, insert
, insertWith
, delete
, filter
, mapMaybe
, lookup
, member
, uncons
, union
, unionWith
, intersection
, intersectionWith
, difference
, mapWithKey
, traverseWithKey
, traverseWithKey_
, unorderedTraverseWithKey_
, foldMapWithKey
, toList
, toMap
, keys
) where
import Control.Applicative ((<|>))
import Data.Data (Data)
import Data.Foldable (traverse_)
import Data.Semigroup
import Prelude hiding (filter, lookup)
import qualified Data.Functor
import qualified Data.Map
import qualified Data.Set
import qualified GHC.Exts
import qualified Prelude
data Map k v = Map (Data.Map.Map k v) [k]
deriving (Data)
instance (Eq k, Eq v) => Eq (Map k v) where
Map m1 ks == Map m2 ks' = m1 == m2 && ks == ks'
{-# INLINABLE (==) #-}
instance (Ord k, Ord v) => Ord (Map k v) where
compare (Map mL ksL) (Map mR ksR) = compare mL mR <> compare ksL ksR
instance Functor (Map k) where
fmap f (Map m ks) = Map (fmap f m) ks
{-# INLINABLE fmap #-}
instance Foldable (Map k) where
foldr f z (Map m _) = foldr f z m
{-# INLINABLE foldr #-}
foldMap f (Map m _) = foldMap f m
{-# INLINABLE foldMap #-}
instance Traversable (Map k) where
traverse f (Map m ks) = (\m' -> Map m' ks) <$> traverse f m
{-# INLINABLE traverse #-}
instance Ord k => Data.Semigroup.Semigroup (Map k v) where
(<>) = union
{-# INLINABLE (<>) #-}
instance Ord k => Monoid (Map k v) where
mempty = Map Data.Map.empty []
{-# INLINABLE mempty #-}
#if !(MIN_VERSION_base(4,11,0))
mappend = (<>)
{-# INLINABLE mappend #-}
#endif
instance (Show k, Show v, Ord k) => Show (Map k v) where
showsPrec d m =
showParen (d > 10) (showString "fromList " . showsPrec 11 kvs)
where
kvs = toList m
instance Ord k => GHC.Exts.IsList (Map k v) where
type Item (Map k v) = (k, v)
fromList = Dhall.Map.fromList
toList = Dhall.Map.toList
singleton :: k -> v -> Map k v
singleton k v = Map m ks
where
m = Data.Map.singleton k v
ks = pure k
{-# INLINABLE singleton #-}
fromList :: Ord k => [(k, v)] -> Map k v
fromList kvs = Map m ks
where
m = Data.Map.fromList kvs
ks = nubOrd (map fst kvs)
{-# INLINABLE fromList #-}
nubOrd :: Ord k => [k] -> [k]
nubOrd = go Data.Set.empty
where
go _ [] = []
go set (k:ks)
| Data.Set.member k set = go set ks
| otherwise = k : go (Data.Set.insert k set) ks
{-# INLINABLE nubOrd #-}
sort :: Ord k => Map k v -> Map k v
sort (Map m _) = Map m ks
where
ks = Data.Map.keys m
{-# INLINABLE sort #-}
isSorted :: Eq k => Map k v -> Bool
isSorted (Map m k) = Data.Map.keys m == k
{-# INLINABLE isSorted #-}
insert :: Ord k => k -> v -> Map k v -> Map k v
insert k v (Map m ks) = Map m' ks'
where
m' = Data.Map.insert k v m
ks' | elem k ks = ks
| otherwise = k : ks
{-# INLINABLE insert #-}
insertWith :: Ord k => (v -> v -> v) -> k -> v -> Map k v -> Map k v
insertWith f k v (Map m ks) = Map m' ks'
where
m' = Data.Map.insertWith f k v m
ks' | elem k ks = ks
| otherwise = k : ks
{-# INLINABLE insertWith #-}
delete :: Ord k => k -> Map k v -> Map k v
delete k (Map m ks) = Map m' ks'
where
m' = Data.Map.delete k m
ks' = Prelude.filter (k /=) ks
{-# INLINABLE delete #-}
filter :: Ord k => (a -> Bool) -> Map k a -> Map k a
filter predicate (Map m ks) = Map m' ks'
where
m' = Data.Map.filter predicate m
set = Data.Map.keysSet m'
ks' = Prelude.filter (\k -> Data.Set.member k set) ks
{-# INLINABLE filter #-}
mapMaybe :: Ord k => (a -> Maybe b) -> Map k a -> Map k b
mapMaybe f (Map m ks) = Map m' ks'
where
m' = Data.Map.mapMaybe f m
set = Data.Map.keysSet m'
ks' = Prelude.filter (\k -> Data.Set.member k set) ks
{-# INLINABLE mapMaybe #-}
lookup :: Ord k => k -> Map k v -> Maybe v
lookup k (Map m _) = Data.Map.lookup k m
{-# INLINABLE lookup #-}
uncons :: Ord k => Map k v -> Maybe (k, v, Map k v)
uncons (Map _ []) = Nothing
uncons (Map m (k:ks)) = Just (k, m Data.Map.! k, Map (Data.Map.delete k m) ks)
{-# INLINABLE uncons #-}
member :: Ord k => k -> Map k v -> Bool
member k (Map m _) = Data.Map.member k m
{-# INLINABLE member #-}
union :: Ord k => Map k v -> Map k v -> Map k v
union (Map mL ksL) (Map mR ksR) = Map m ks
where
m = Data.Map.union mL mR
setL = Data.Map.keysSet mL
ks = ksL <|> Prelude.filter (\k -> Data.Set.notMember k setL) ksR
{-# INLINABLE union #-}
unionWith :: Ord k => (v -> v -> v) -> Map k v -> Map k v -> Map k v
unionWith combine (Map mL ksL) (Map mR ksR) = Map m ks
where
m = Data.Map.unionWith combine mL mR
setL = Data.Map.keysSet mL
ks = ksL <|> Prelude.filter (\k -> Data.Set.notMember k setL) ksR
{-# INLINABLE unionWith #-}
intersection :: Ord k => Map k a -> Map k b -> Map k a
intersection (Map mL ksL) (Map mR _) = Map m ks
where
m = Data.Map.intersection mL mR
setL = Data.Map.keysSet mL
setR = Data.Map.keysSet mR
set = Data.Set.intersection setL setR
ks = Prelude.filter (\k -> Data.Set.member k set) ksL
{-# INLINABLE intersection #-}
intersectionWith :: Ord k => (a -> b -> c) -> Map k a -> Map k b -> Map k c
intersectionWith combine (Map mL ksL) (Map mR _) = Map m ks
where
m = Data.Map.intersectionWith combine mL mR
setL = Data.Map.keysSet mL
setR = Data.Map.keysSet mR
set = Data.Set.intersection setL setR
ks = Prelude.filter (\k -> Data.Set.member k set) ksL
{-# INLINABLE intersectionWith #-}
difference :: Ord k => Map k a -> Map k b -> Map k a
difference (Map mL ksL) (Map mR _) = Map m ks
where
m = Data.Map.difference mL mR
setR = Data.Map.keysSet mR
ks = Prelude.filter (\k -> Data.Set.notMember k setR) ksL
{-# INLINABLE difference #-}
foldMapWithKey :: (Monoid m, Ord k) => (k -> a -> m) -> Map k a -> m
foldMapWithKey f m = foldMap (uncurry f) (toList m)
{-# INLINABLE foldMapWithKey #-}
mapWithKey :: (k -> a -> b) -> Map k a -> Map k b
mapWithKey f (Map m ks) = Map m' ks
where
m' = Data.Map.mapWithKey f m
{-# INLINABLE mapWithKey #-}
traverseWithKey
:: Ord k => Applicative f => (k -> a -> f b) -> Map k a -> f (Map k b)
traverseWithKey f m =
fmap fromList (traverse f' (toList m))
where
f' (k, a) = fmap ((,) k) (f k a)
{-# INLINABLE traverseWithKey #-}
traverseWithKey_
:: Ord k => Applicative f => (k -> a -> f ()) -> Map k a -> f ()
traverseWithKey_ f m = Data.Functor.void (traverseWithKey f m)
{-# INLINABLE traverseWithKey_ #-}
unorderedTraverseWithKey_
:: Ord k => Applicative f => (k -> a -> f ()) -> Map k a -> f ()
unorderedTraverseWithKey_ f = Data.Functor.void . traverse_ (uncurry f) . toList
{-# INLINABLE unorderedTraverseWithKey_ #-}
toList :: Ord k => Map k v -> [(k, v)]
toList (Map m ks) = fmap (\k -> (k, m Data.Map.! k)) ks
{-# INLINABLE toList #-}
toMap :: Map k v -> Data.Map.Map k v
toMap (Map m _) = m
{-# INLINABLE toMap #-}
keys :: Map k v -> [k]
keys (Map _ ks) = ks
{-# INLINABLE keys #-}