diff options
Diffstat (limited to 'src')
| -rw-r--r-- | src/Data/Dependent/EnumMap/Strict/Internal.hs | 54 |
1 files changed, 27 insertions, 27 deletions
diff --git a/src/Data/Dependent/EnumMap/Strict/Internal.hs b/src/Data/Dependent/EnumMap/Strict/Internal.hs index c0b47ab..00cc169 100644 --- a/src/Data/Dependent/EnumMap/Strict/Internal.hs +++ b/src/Data/Dependent/EnumMap/Strict/Internal.hs @@ -83,7 +83,7 @@ dSumToKV (k :=> v) = let (i, inf) = fromEnum1 k in (i, KV inf v) -- | Assumes that the input was obtained via 'fromEnum1'. kVToDSum :: Enum1 k => (Int, KV k v) -> DSum k v -kVToDSum (i, KV inf v) = case toEnum1 i inf of k -> k :=> coe1 v +kVToDSum (i, KV inf v) = case toEnum1 i inf of k -> k :=> v -- * Construction @@ -120,7 +120,7 @@ fromListWithKey f l = DEnumMap (IM.fromListWithKey (\i (KV inf1 v1) (KV inf2 v2) -> case toEnum1 i inf1 of - k1 -> typeCheck1 k1 i inf2 $ KV inf1 (f k1 (coe1 v1) (coe1 v2))) + k1 -> typeCheck1 k1 i inf2 $ KV inf1 (f k1 v1 (coe1 v2))) (dSumToKV <$> l)) -- ** From Ascending Lists @@ -145,7 +145,7 @@ fromAscListWithKey f l = DEnumMap (IM.fromAscListWithKey (\i (KV inf1 v1) (KV inf2 v2) -> case toEnum1 i inf1 of - k1 -> typeCheck1 k1 i inf2 $ KV inf1 (f k1 (coe1 v1) (coe1 v2))) + k1 -> typeCheck1 k1 i inf2 $ KV inf1 (f k1 v1 (coe1 v2))) (dSumToKV <$> l)) fromDistinctAscList :: Enum1 k => [DSum k v] -> DEnumMap k v @@ -305,7 +305,7 @@ unionWithKey f (DEnumMap m1 :: DEnumMap k v) (DEnumMap m2) = DEnumMap (IM.unionW where f' :: Int -> KV k v -> KV k v -> KV k v f' i (KV inf1 v1) (KV inf2 v2) = case toEnum1 i inf1 of - k1 -> typeCheck1 k1 i inf2 $ KV inf1 (f k1 (coe1 v1) (coe1 v2)) + k1 -> typeCheck1 k1 i inf2 $ KV inf1 (f k1 v1 (coe1 v2)) unions :: (Foldable f, Enum1 k, TestEquality k) => f (DEnumMap k v) -> DEnumMap k v unions = Foldable.foldl' union empty @@ -328,7 +328,7 @@ differenceWith f (DEnumMap m1) (DEnumMap m2) = DEnumMap (IM.differenceWithKey f' where f' :: Int -> KV k v1 -> KV k v2 -> Maybe (KV k v1) f' i (KV inf1 v1) (KV inf2 v2) = - typeCheck2 (Proxy @k) i inf1 inf2 $ KV inf1 <$> f (coe1 v1) (coe1 v2) + typeCheck2 (Proxy @k) i inf1 inf2 $ KV inf1 <$> f v1 (coe1 v2) differenceWithKey :: forall k v1 v2. (Enum1 k, TestEquality k) => (forall a. k a -> v1 a -> v2 a -> Maybe (v1 a)) -> DEnumMap k v1 -> DEnumMap k v2 -> DEnumMap k v1 @@ -336,7 +336,7 @@ differenceWithKey f (DEnumMap m1) (DEnumMap m2) = DEnumMap (IM.differenceWithKey where f' :: Int -> KV k v1 -> KV k v2 -> Maybe (KV k v1) f' i (KV inf1 v1) (KV inf2 v2) = case toEnum1 i inf1 of - k1 -> typeCheck1 k1 i inf2 $ KV inf1 <$> f k1 (coe1 v1) (coe1 v2) + k1 -> typeCheck1 k1 i inf2 $ KV inf1 <$> f k1 v1 (coe1 v2) -- | Because the underlying maps are keyed on integers, it is possible to -- subtract a map from another even if the key types differ. This function @@ -354,7 +354,7 @@ differenceWithKey' f (DEnumMap m1) (DEnumMap m2) = DEnumMap (IM.differenceWithKe where f' :: Int -> KV k1 v1 -> KV k2 v2 -> Maybe (KV k1 v1) f' i (KV inf1 v1) (KV inf2 v2) = case (toEnum1 i inf1, toEnum1 i inf2) of - (k1, k2) -> KV inf1 <$> f k1 (coe1 v1) k2 (coe1 v2) + (k1, k2) -> KV inf1 <$> f k1 v1 k2 v2 -- ** Intersection @@ -367,7 +367,7 @@ intersectionWith f (DEnumMap m1) (DEnumMap m2) = DEnumMap (IM.intersectionWithKe where f' :: Int -> KV k v1 -> KV k v2 -> KV k v3 f' i (KV inf1 v1) (KV inf2 v2) = - typeCheck2 (Proxy @k) i inf1 inf2 $ KV inf1 $ f (coe1 v1) (coe1 v2) + typeCheck2 (Proxy @k) i inf1 inf2 $ KV inf1 $ f v1 (coe1 v2) intersectionWithKey :: forall k v1 v2 v3. (Enum1 k, TestEquality k) => (forall a. k a -> v1 a -> v2 a -> v3 a) -> DEnumMap k v1 -> DEnumMap k v2 -> DEnumMap k v3 @@ -375,7 +375,7 @@ intersectionWithKey f (DEnumMap m1) (DEnumMap m2) = DEnumMap (IM.intersectionWit where f' :: Int -> KV k v1 -> KV k v2 -> KV k v3 f' i (KV inf1 v1) (KV inf2 v2) = case toEnum1 i inf1 of - k1 -> typeCheck1 k1 i inf2 $ KV inf1 $ f k1 (coe1 v1) (coe1 v2) + k1 -> typeCheck1 k1 i inf2 $ KV inf1 $ f k1 v1 (coe1 v2) -- | Generalises 'intersectionWithKey' in the same way as 'differenceWithKey'' -- generalises 'differenceWithKey'. @@ -386,7 +386,7 @@ intersectionWithKey' f (DEnumMap m1) (DEnumMap m2) = DEnumMap (IM.intersectionWi where f' :: Int -> KV k1 v1 -> KV k2 v2 -> KV k1 v3 f' i (KV inf1 v1) (KV inf2 v2) = case (toEnum1 i inf1, toEnum1 i inf2) of - (k1, k2) -> KV inf1 $ f k1 (coe1 v1) k2 (coe1 v2) + (k1, k2) -> KV inf1 $ f k1 v1 k2 (coe1 v2) -- ** Disjoint @@ -411,7 +411,7 @@ mergeWithKey f g1 g2 (DEnumMap m1) (DEnumMap m2) = where f' :: Int -> KV k v1 -> KV k v2 -> Maybe (KV k v3) f' i (KV inf1 v1) (KV inf2 v2) = case toEnum1 i inf1 of - k1 -> typeCheck1 k1 i inf2 $ KV inf1 <$> f k1 (coe1 v1) (coe1 v2) + k1 -> typeCheck1 k1 i inf2 $ KV inf1 <$> f k1 v1 (coe1 v2) -- * Traversal -- ** Map @@ -421,28 +421,28 @@ map f = mapWithKey (const f) mapWithKey :: Enum1 k => (forall a. k a -> v1 a -> v2 a) -> DEnumMap k v1 -> DEnumMap k v2 mapWithKey f (DEnumMap m) = - DEnumMap (IM.mapWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf $ f k (coe1 v)) m) + DEnumMap (IM.mapWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf $ f k v) m) traverseWithKey :: (Applicative f, Enum1 k) => (forall a. k a -> v1 a -> f (v2 a)) -> DEnumMap k v1 -> f (DEnumMap k v2) traverseWithKey f (DEnumMap m) = - DEnumMap <$> IM.traverseWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k (coe1 v)) m + DEnumMap <$> IM.traverseWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k v) m traverseMaybeWithKey :: (Applicative f, Enum1 k) => (forall a. k a -> v1 a -> f (Maybe (v2 a))) -> DEnumMap k v1 -> f (DEnumMap k v2) traverseMaybeWithKey f (DEnumMap m) = - DEnumMap <$> IM.traverseMaybeWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> fmap (KV inf) <$> f k (coe1 v)) m + DEnumMap <$> IM.traverseMaybeWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> fmap (KV inf) <$> f k v) m mapAccum :: Enum1 k => (forall a. acc -> v1 a -> (acc, v2 a)) -> acc -> DEnumMap k v1 -> (acc, DEnumMap k v2) mapAccum f = mapAccumWithKey (\x _ y -> f x y) mapAccumWithKey :: Enum1 k => (forall a. acc -> k a -> v1 a -> (acc, v2 a)) -> acc -> DEnumMap k v1 -> (acc, DEnumMap k v2) mapAccumWithKey f acc0 (DEnumMap m) = - second DEnumMap $ IM.mapAccumWithKey (\acc i (KV inf v) -> case toEnum1 i inf of k -> second (KV inf) $ f acc k (coe1 v)) acc0 m + second DEnumMap $ IM.mapAccumWithKey (\acc i (KV inf v) -> case toEnum1 i inf of k -> second (KV inf) $ f acc k v) acc0 m mapAccumRWithKey :: Enum1 k => (forall a. acc -> k a -> v1 a -> (acc, v2 a)) -> acc -> DEnumMap k v1 -> (acc, DEnumMap k v2) mapAccumRWithKey f acc0 (DEnumMap m) = - second DEnumMap $ IM.mapAccumRWithKey (\acc i (KV inf v) -> case toEnum1 i inf of k -> second (KV inf) $ f acc k (coe1 v)) acc0 m + second DEnumMap $ IM.mapAccumRWithKey (\acc i (KV inf v) -> case toEnum1 i inf of k -> second (KV inf) $ f acc k v) acc0 m -- TODO: These are hard. Probably we can't avoid using a fold, analogously as in IntMap. -- mapKeys @@ -459,15 +459,15 @@ foldl f acc0 (DEnumMap m) = IM.foldl (\acc (KV _ v) -> f acc v) acc0 m foldrWithKey :: Enum1 k => (forall a. k a -> v a -> acc -> acc) -> acc -> DEnumMap k v -> acc foldrWithKey f acc0 (DEnumMap m) = - IM.foldrWithKey (\i (KV inf v) acc -> case toEnum1 i inf of k -> f k (coe1 v) acc) acc0 m + IM.foldrWithKey (\i (KV inf v) acc -> case toEnum1 i inf of k -> f k v acc) acc0 m foldlWithKey :: Enum1 k => (forall a. acc -> k a -> v a -> acc) -> acc -> DEnumMap k v -> acc foldlWithKey f acc0 (DEnumMap m) = - IM.foldlWithKey (\acc i (KV inf v) -> case toEnum1 i inf of k -> f acc k (coe1 v)) acc0 m + IM.foldlWithKey (\acc i (KV inf v) -> case toEnum1 i inf of k -> f acc k v) acc0 m foldMapWithKey :: (Monoid m, Enum1 k) => (forall a. k a -> v a -> m) -> DEnumMap k v -> m foldMapWithKey f (DEnumMap m) = - IM.foldMapWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> f k (coe1 v)) m + IM.foldMapWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> f k v) m -- ** Strict folds @@ -479,11 +479,11 @@ foldl' f acc0 (DEnumMap m) = IM.foldl' (\acc (KV _ v) -> f acc v) acc0 m foldrWithKey' :: Enum1 k => (forall a. k a -> v a -> acc -> acc) -> acc -> DEnumMap k v -> acc foldrWithKey' f acc0 (DEnumMap m) = - IM.foldrWithKey' (\i (KV inf v) acc -> case toEnum1 i inf of k -> f k (coe1 v) acc) acc0 m + IM.foldrWithKey' (\i (KV inf v) acc -> case toEnum1 i inf of k -> f k v acc) acc0 m foldlWithKey' :: Enum1 k => (forall a. acc -> k a -> v a -> acc) -> acc -> DEnumMap k v -> acc foldlWithKey' f acc0 (DEnumMap m) = - IM.foldlWithKey' (\acc i (KV inf v) -> case toEnum1 i inf of k -> f acc k (coe1 v)) acc0 m + IM.foldlWithKey' (\acc i (KV inf v) -> case toEnum1 i inf of k -> f acc k v) acc0 m -- * Conversion @@ -519,7 +519,7 @@ filter f (DEnumMap m) = DEnumMap (IM.filter (\(KV _ v) -> f v) m) filterWithKey :: Enum1 k => (forall a. k a -> v a -> Bool) -> DEnumMap k v -> DEnumMap k v filterWithKey f (DEnumMap m) = - DEnumMap (IM.filterWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> f k (coe1 v)) m) + DEnumMap (IM.filterWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> f k v) m) -- TODO: Wait for DEnumSet. -- restrictKeys @@ -531,7 +531,7 @@ partition f (DEnumMap m) = partitionWithKey :: Enum1 k => (forall a. k a -> v a -> Bool) -> DEnumMap k v -> (DEnumMap k v, DEnumMap k v) partitionWithKey f (DEnumMap m) = - bimap DEnumMap DEnumMap (IM.partitionWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> f k (coe1 v)) m) + bimap DEnumMap DEnumMap (IM.partitionWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> f k v) m) -- | \(O(\min(n,W)^2)\). Because of the lack of a @takeWhileAntitoneWithValue@ -- operation on 'Data.IntMap.Strict.IntMap', this function performs additional lookups to @@ -557,7 +557,7 @@ mapMaybe f = mapMaybeWithKey (const f) mapMaybeWithKey :: Enum1 k => (forall a. k a -> v1 a -> Maybe (v2 a)) -> DEnumMap k v1 -> DEnumMap k v2 mapMaybeWithKey f (DEnumMap m) = - DEnumMap (IM.mapMaybeWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k (coe1 v)) m) + DEnumMap (IM.mapMaybeWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k v) m) mapEither :: Enum1 k => (forall a. v1 a -> Either (v2 a) (v3 a)) -> DEnumMap k v1 -> (DEnumMap k v2, DEnumMap k v3) @@ -566,7 +566,7 @@ mapEither f = mapEitherWithKey (const f) mapEitherWithKey :: Enum1 k => (forall a. k a -> v1 a -> Either (v2 a) (v3 a)) -> DEnumMap k v1 -> (DEnumMap k v2, DEnumMap k v3) mapEitherWithKey f (DEnumMap m) = - bimap DEnumMap DEnumMap (IM.mapEitherWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> bimap (KV inf) (KV inf) $ f k (coe1 v)) m) + bimap DEnumMap DEnumMap (IM.mapEitherWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> bimap (KV inf) (KV inf) $ f k v) m) split :: Enum1 k => k a -> DEnumMap k v -> (DEnumMap k v, DEnumMap k v) split k (DEnumMap m) = bimap DEnumMap DEnumMap (IM.split (fst $ fromEnum1 k) m) @@ -628,14 +628,14 @@ updateMin f = updateMinWithKey (const f) updateMinWithKey :: Enum1 k => (forall a. k a -> v a -> Maybe (v a)) -> DEnumMap k v -> DEnumMap k v updateMinWithKey f (DEnumMap m) = - DEnumMap (IM.updateMinWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k (coe1 v)) m) + DEnumMap (IM.updateMinWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k v) m) updateMax :: Enum1 k => (forall a. v a -> Maybe (v a)) -> DEnumMap k v -> DEnumMap k v updateMax f = updateMaxWithKey (const f) updateMaxWithKey :: Enum1 k => (forall a. k a -> v a -> Maybe (v a)) -> DEnumMap k v -> DEnumMap k v updateMaxWithKey f (DEnumMap m) = - DEnumMap (IM.updateMaxWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k (coe1 v)) m) + DEnumMap (IM.updateMaxWithKey (\i (KV inf v) -> case toEnum1 i inf of k -> KV inf <$> f k v) m) minView :: DEnumMap k v -> Maybe (v a, DEnumMap k v) minView (DEnumMap m) = bimap (\(KV _ v) -> coe1 v) DEnumMap <$> IM.minView m |
