summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2019-07-16 14:46:48 -0400
committerJoe Crayne <joe@jerkface.net>2019-07-16 14:46:48 -0400
commit46bbdd047e7dfba3fe95e8b8f5c9e729d4268862 (patch)
tree51689eb8be09300aeff512f50226d186a4141122
parent4ed990981e5bf0b3902364b6b09919d3d7d976cc (diff)
Updates to IntMapClass.
-rw-r--r--lib/IntMapClass.hs98
1 files changed, 53 insertions, 45 deletions
diff --git a/lib/IntMapClass.hs b/lib/IntMapClass.hs
index 3d08e46..b44e05c 100644
--- a/lib/IntMapClass.hs
+++ b/lib/IntMapClass.hs
@@ -5,6 +5,7 @@
5 DeriveDataTypeable #-} 5 DeriveDataTypeable #-}
6module IntMapClass where 6module IntMapClass where
7 7
8import Control.Arrow (second)
8import qualified Data.IntMap.Strict as IntMap 9import qualified Data.IntMap.Strict as IntMap
9import Data.IntMap.Strict ( IntMap ) 10import Data.IntMap.Strict ( IntMap )
10import Data.Typeable ( Typeable ) 11import Data.Typeable ( Typeable )
@@ -32,7 +33,13 @@ newtype IMap k a = IMap { intmap :: IntMap a }
32 , NFData 33 , NFData
33 ) 34 )
34 35
36adapt_k_a_m :: Coercible k1 Int =>
37 (Int -> t -> IntMap a -> x) -> k1 -> t -> IMap k2 a -> x
35adaptm_k_a_m f k a m = IMap $ adapt_k_a_m f k a m 38adaptm_k_a_m f k a m = IMap $ adapt_k_a_m f k a m
39
40adaptm_k_a_m :: Coercible k1 Int =>
41 (Int -> t -> IntMap a1 -> IntMap a2)
42 -> k1 -> t -> IMap k2 a1 -> IMap k3 a2
36adapt_k_a_m f k a m = adapt_m (adapt_k f k a) m 43adapt_k_a_m f k a m = adapt_m (adapt_k f k a) m
37 44
38adapt_m_k :: Coercible k Int => (IntMap a -> Int -> x) -> IMap k a -> k -> x 45adapt_m_k :: Coercible k Int => (IntMap a -> Int -> x) -> IMap k a -> k -> x
@@ -60,17 +67,16 @@ adaptm_m_m f a b = IMap $ adapt_m_m f a b
60adapt_m :: (IntMap a -> x) -> IMap k a -> x 67adapt_m :: (IntMap a -> x) -> IMap k a -> x
61adapt_m f (IMap m) = f m 68adapt_m f (IMap m) = f m
62 69
63first f (x,y) = (f x,y)
64second f (x,y) = (x,f y)
65
66
67(!) :: Coercible k Int => IMap k a -> k -> a 70(!) :: Coercible k Int => IMap k a -> k -> a
68(!) = adapt_m_k (IntMap.!) 71(!) = adapt_m_k (IntMap.!)
69 72
70(\\) :: IMap k a -> IMap k a -> IMap k a 73(\\) :: IMap k a -> IMap k a -> IMap k a
71(\\) a b = IMap $ adapt_m_m (IntMap.\\) a b 74(\\) a b = IMap $ adapt_m_m (IntMap.\\) a b
72 75
76null :: IMap k a -> Bool
73null = adapt_m (IntMap.null) 77null = adapt_m (IntMap.null)
78
79size :: IMap k a -> Int
74size = adapt_m (IntMap.size) 80size = adapt_m (IntMap.size)
75 81
76member :: Coercible k Int => k -> IMap k a -> Bool 82member :: Coercible k Int => k -> IMap k a -> Bool
@@ -85,16 +91,19 @@ lookup = adapt_k_m (IntMap.lookup)
85findWithDefault :: Coercible k Int => x -> k -> IMap k x -> x 91findWithDefault :: Coercible k Int => x -> k -> IMap k x -> x
86findWithDefault a = adapt_k_m (IntMap.findWithDefault a) 92findWithDefault a = adapt_k_m (IntMap.findWithDefault a)
87 93
88-- FIXME: fmap (first coerce) probably incurs cost 94lookupLT :: Coercible Int k => k -> IMap k a -> Maybe (k, a)
89lookupLT :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a) 95lookupLT k (IMap m) = coerce $ IntMap.lookupLT (coerce k) m
90lookupLT k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupLT) k m
91lookupGT :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a)
92lookupGT k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupGT) k m
93lookupLE :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a)
94lookupLE k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupLE) k m
95lookupGE :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a)
96lookupGE k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupGE) k m
97 96
97lookupGT :: Coercible Int k => k -> IMap k a -> Maybe (k, a)
98lookupGT k (IMap m) = coerce $ IntMap.lookupGT (coerce k) m
99
100lookupLE :: Coercible Int k => k -> IMap k a -> Maybe (k, a)
101lookupLE k (IMap m) = coerce $ IntMap.lookupLE (coerce k) m
102
103lookupGE :: Coercible Int k => k -> IMap k a -> Maybe (k, a)
104lookupGE k (IMap m) = coerce $ IntMap.lookupGE (coerce k) m
105
106empty :: IMap k a
98empty = IMap IntMap.empty 107empty = IMap IntMap.empty
99 108
100singleton :: Coercible k Int => k -> a -> IMap k a 109singleton :: Coercible k Int => k -> a -> IMap k a
@@ -106,10 +115,10 @@ insert = adaptm_k_a_m IntMap.insert
106insertWith :: Coercible k Int => (a -> a -> a) -> k -> a -> IMap k a -> IMap k a 115insertWith :: Coercible k Int => (a -> a -> a) -> k -> a -> IMap k a -> IMap k a
107insertWith f = adaptm_k_a_m (IntMap.insertWith f) 116insertWith f = adaptm_k_a_m (IntMap.insertWith f)
108 117
109insertWithKey :: (Coercible Int k, Coercible k Int) => (k -> a -> a -> a) -> k -> a -> IMap k a -> IMap k a 118insertWithKey :: Coercible Int k => (k -> a -> a -> a) -> k -> a -> IMap k a -> IMap k a
110insertWithKey f = adaptm_k_a_m (IntMap.insertWithKey $ f . coerce) 119insertWithKey f = adaptm_k_a_m (IntMap.insertWithKey $ f . coerce)
111 120
112insertLookupWithKey :: (Coercible Int k, Coercible k Int) => 121insertLookupWithKey :: Coercible Int k =>
113 (k -> a -> a -> a) -> k -> a -> IMap k a -> (Maybe a, IMap k a) 122 (k -> a -> a -> a) -> k -> a -> IMap k a -> (Maybe a, IMap k a)
114insertLookupWithKey f k a m = second IMap $ adapt_k_a_m (IntMap.insertLookupWithKey $ f . coerce) k a m 123insertLookupWithKey f k a m = second IMap $ adapt_k_a_m (IntMap.insertLookupWithKey $ f . coerce) k a m
115 124
@@ -119,7 +128,7 @@ delete = adaptm_k_m IntMap.delete
119adjust :: Coercible k Int => (a -> a) -> k -> IMap k a -> IMap k a 128adjust :: Coercible k Int => (a -> a) -> k -> IMap k a -> IMap k a
120adjust f = adaptm_k_m (IntMap.adjust f) 129adjust f = adaptm_k_m (IntMap.adjust f)
121 130
122adjustWithKey :: ( Coercible Int k, Coercible k Int ) => 131adjustWithKey :: Coercible Int k =>
123 (k -> a -> a) -> k -> IMap k a -> IMap k a 132 (k -> a -> a) -> k -> IMap k a -> IMap k a
124adjustWithKey f = adaptm_k_m (IntMap.adjustWithKey $ f . coerce) 133adjustWithKey f = adaptm_k_m (IntMap.adjustWithKey $ f . coerce)
125 134
@@ -128,13 +137,11 @@ update
128update f = adaptm_k_m (IntMap.update f) 137update f = adaptm_k_m (IntMap.update f)
129 138
130 139
131updateWithKey 140updateWithKey :: Coercible Int k =>
132 :: (Coercible k Int, Coercible Int k) =>
133 (k -> a -> Maybe a) -> k -> IMap k a -> IMap k a 141 (k -> a -> Maybe a) -> k -> IMap k a -> IMap k a
134updateWithKey f = adaptm_k_m (IntMap.updateWithKey $ f . coerce) 142updateWithKey f = adaptm_k_m (IntMap.updateWithKey $ f . coerce)
135 143
136updateLookupWithKey :: 144updateLookupWithKey :: Coercible k Int =>
137 (Coercible k Int, Coercible Int k) =>
138 (k -> a -> Maybe a) -> k -> IMap k a -> (Maybe a, IMap k a) 145 (k -> a -> Maybe a) -> k -> IMap k a -> (Maybe a, IMap k a)
139updateLookupWithKey f k m = 146updateLookupWithKey f k m =
140 second IMap $ adapt_k_m (IntMap.updateLookupWithKey $ f . coerce) k m 147 second IMap $ adapt_k_m (IntMap.updateLookupWithKey $ f . coerce) k m
@@ -158,8 +165,11 @@ unionWithKey f = adaptm_m_m (IntMap.unionWithKey $ f . coerce)
158-- unionsWith :: Coercible [IMap k a] [IntMap a] => (a->a->a) -> [IMap k a] -> IMap k a 165-- unionsWith :: Coercible [IMap k a] [IntMap a] => (a->a->a) -> [IMap k a] -> IMap k a
159-- unionsWith f ms = IMap $ IntMap.unionsWith f (coerce ms) 166-- unionsWith f ms = IMap $ IntMap.unionsWith f (coerce ms)
160 167
168difference :: IMap k b -> IMap k b -> IMap k b
161difference = adaptm_m_m IntMap.difference 169difference = adaptm_m_m IntMap.difference
162 170
171differenceWith :: (b -> b -> Maybe b)
172 -> IMap k b -> IMap k b -> IMap k b
163differenceWith f = adaptm_m_m (IntMap.differenceWith f) 173differenceWith f = adaptm_m_m (IntMap.differenceWith f)
164 174
165differenceWithKey :: 175differenceWithKey ::
@@ -167,7 +177,10 @@ differenceWithKey ::
167 (k -> a -> a -> Maybe a) -> IMap k a -> IMap k a -> IMap k a 177 (k -> a -> a -> Maybe a) -> IMap k a -> IMap k a -> IMap k a
168differenceWithKey f = adaptm_m_m (IntMap.differenceWithKey $ f . coerce) 178differenceWithKey f = adaptm_m_m (IntMap.differenceWithKey $ f . coerce)
169 179
180intersection :: IMap k b -> IMap k b -> IMap k b
170intersection = adaptm_m_m IntMap.intersection 181intersection = adaptm_m_m IntMap.intersection
182
183intersectionWith :: (a -> a -> a) -> IMap k a -> IMap k a -> IMap k a
171intersectionWith f = adaptm_m_m (IntMap.intersectionWith f) 184intersectionWith f = adaptm_m_m (IntMap.intersectionWith f)
172 185
173mergeWithKey :: 186mergeWithKey ::
@@ -211,15 +224,15 @@ mapAccumRWithKey :: Coercible Int k =>
211mapAccumRWithKey f a m = second IMap $ IntMap.mapAccumRWithKey f' a (intmap m) 224mapAccumRWithKey f a m = second IMap $ IntMap.mapAccumRWithKey f' a (intmap m)
212 where f' a k b = f a (coerce k) b 225 where f' a k b = f a (coerce k) b
213 226
214mapKeys :: (Coercible Int k1, Coercible k2 Int) => 227mapKeys :: (Coercible Int k1, Coercible Int k2) =>
215 (k1 -> k2) -> IMap k1 a -> IMap k2 a 228 (k1 -> k2) -> IMap k1 a -> IMap k2 a
216mapKeys f = IMap . adapt_m (IntMap.mapKeys (coerce . f . coerce)) 229mapKeys f = IMap . adapt_m (IntMap.mapKeys (coerce . f . coerce))
217 230
218mapKeysWith :: (Coercible Int k1, Coercible k2 Int) => 231mapKeysWith :: (Coercible Int k1, Coercible Int k2) =>
219 (a->a->a) -> (k1 -> k2) -> IMap k1 a -> IMap k2 a 232 (a->a->a) -> (k1 -> k2) -> IMap k1 a -> IMap k2 a
220mapKeysWith c f = IMap . adapt_m (IntMap.mapKeysWith c (coerce . f . coerce)) 233mapKeysWith c f = IMap . adapt_m (IntMap.mapKeysWith c (coerce . f . coerce))
221 234
222mapKeysMonotonic :: (Coercible Int k1, Coercible k2 Int) => 235mapKeysMonotonic :: (Coercible Int k1, Coercible Int k2) =>
223 (k1 -> k2) -> IMap k1 a -> IMap k2 a 236 (k1 -> k2) -> IMap k1 a -> IMap k2 a
224mapKeysMonotonic f = IMap . adapt_m (IntMap.mapKeysMonotonic (coerce . f . coerce)) 237mapKeysMonotonic f = IMap . adapt_m (IntMap.mapKeysMonotonic (coerce . f . coerce))
225 238
@@ -236,7 +249,7 @@ foldlWithKey ::
236 Coercible Int k => (x -> k -> a -> x) -> x -> IMap k a -> x 249 Coercible Int k => (x -> k -> a -> x) -> x -> IMap k a -> x
237foldlWithKey f a = adapt_m (IntMap.foldlWithKey f' a) where f' a = f a . coerce 250foldlWithKey f a = adapt_m (IntMap.foldlWithKey f' a) where f' a = f a . coerce
238 251
239foldMapWithKey :: (Monoid m, Coercible k Int) => (k -> a -> m) -> IMap k a -> m 252foldMapWithKey :: (Monoid m, Coercible Int k) => (k -> a -> m) -> IMap k a -> m
240foldMapWithKey f = adapt_m (IntMap.foldMapWithKey $ f . coerce) 253foldMapWithKey f = adapt_m (IntMap.foldMapWithKey $ f . coerce)
241 254
242foldr' :: (a -> x -> x) -> x -> IMap k a -> x 255foldr' :: (a -> x -> x) -> x -> IMap k a -> x
@@ -255,50 +268,47 @@ foldlWithKey' f a = adapt_m (IntMap.foldlWithKey' f' a) where f' a = f a . coerc
255elems :: IMap k a -> [a] 268elems :: IMap k a -> [a]
256elems = IntMap.elems . intmap 269elems = IntMap.elems . intmap
257 270
258keys :: Coercible [Int] [k] => IMap k a -> [k] 271keys :: Coercible Int k => IMap k a -> [k]
259keys = coerce . IntMap.keys . intmap 272keys = coerce . IntMap.keys . intmap
260 273
261assocs :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k, a)] 274assocs :: Coercible Int k => IMap k a -> [(k, a)]
262assocs = coerce . IntMap.assocs . intmap 275assocs = coerce . IntMap.assocs . intmap
263 276
264-- Not implementing... (doing it right requires wrapping IntSet) 277-- Not implementing... (doing it right requires wrapping IntSet)
265-- keysSet :: IntMap a -> IntSet 278-- keysSet :: IntMap a -> IntSet
266-- fromSet :: (Key -> a) -> IntSet -> IntMap a 279-- fromSet :: (Key -> a) -> IntSet -> IntMap a
267 280
268toList :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k, a)] 281toList :: Coercible Int k => IMap k a -> [(k, a)]
269toList = coerce . IntMap.toList . intmap 282toList = coerce . IntMap.toList . intmap
270 283
271fromList :: Coercible [(k,a)] [(Int,a)] => [(k, a)] -> IMap k a 284fromList :: Coercible Int k => [(k, a)] -> IMap k a
272fromList = IMap . IntMap.fromList . coerce 285fromList = IMap . IntMap.fromList . coerce
273 286
274fromListWith :: Coercible [(k,a)] [(Int,a)] => (a -> a -> a) -> [(k, a)] -> IMap k a 287fromListWith :: Coercible Int k => (a -> a -> a) -> [(k, a)] -> IMap k a
275fromListWith f = IMap . IntMap.fromListWith f . coerce 288fromListWith f = IMap . IntMap.fromListWith f . coerce
276 289
277fromListWithKey :: ( Coercible Int k 290fromListWithKey :: Coercible Int k =>
278 , Coercible [(k,a)] [(Int,a)] ) =>
279 (k -> a -> a -> a) -> [(k, a)] -> IMap k a 291 (k -> a -> a -> a) -> [(k, a)] -> IMap k a
280fromListWithKey f = IMap . IntMap.fromListWithKey (f . coerce) . coerce 292fromListWithKey f = IMap . IntMap.fromListWithKey (f . coerce) . coerce
281 293
282toAscList :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k,a)] 294toAscList :: Coercible Int k => IMap k a -> [(k,a)]
283toAscList (IMap m) = coerce $ IntMap.toAscList m 295toAscList (IMap m) = coerce $ IntMap.toAscList m
284 296
285toDescList :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k,a)] 297toDescList :: Coercible Int k => IMap k a -> [(k,a)]
286toDescList (IMap m) = coerce $ IntMap.toDescList m 298toDescList (IMap m) = coerce $ IntMap.toDescList m
287 299
288fromAscList :: Coercible [(k,a)] [(Int,a)] => [(k, a)] -> IMap k a 300fromAscList :: Coercible Int k => [(k, a)] -> IMap k a
289fromAscList = IMap . IntMap.fromAscList . coerce 301fromAscList = IMap . IntMap.fromAscList . coerce
290 302
291fromAscListWith :: 303fromAscListWith :: Coercible Int k
292 Coercible [(k,a)] [(Int, a)] => 304 => (a -> a -> a) -> [(k,a)] -> IMap k a
293 (a -> a -> a) -> [(k,a)] -> IMap k a
294fromAscListWith f = IMap . IntMap.fromAscListWith f . coerce 305fromAscListWith f = IMap . IntMap.fromAscListWith f . coerce
295 306
296fromAscListWithKey :: 307fromAscListWithKey :: Coercible Int k
297 (Coercible Int k, Coercible [(k,a)] [(Int, a)]) => 308 => (k -> a -> a -> a) -> [(k,a)] -> IMap k a
298 (k -> a -> a -> a) -> [(k,a)] -> IMap k a
299fromAscListWithKey f = IMap . IntMap.fromAscListWithKey (f . coerce) . coerce 309fromAscListWithKey f = IMap . IntMap.fromAscListWithKey (f . coerce) . coerce
300 310
301fromDistinctAscList :: Coercible [(k,a)] [(Int,a)] => [(k, a)] -> IMap k a 311fromDistinctAscList :: Coercible Int k => [(k, a)] -> IMap k a
302fromDistinctAscList = IMap . IntMap.fromDistinctAscList . coerce 312fromDistinctAscList = IMap . IntMap.fromDistinctAscList . coerce
303 313
304filter :: (a -> Bool) -> IMap k a -> IMap k a 314filter :: (a -> Bool) -> IMap k a -> IMap k a
@@ -307,13 +317,11 @@ filter f = IMap . adapt_m (IntMap.filter f)
307filterWithKey :: Coercible Int k => (k -> a -> Bool) -> IMap k a -> IMap k a 317filterWithKey :: Coercible Int k => (k -> a -> Bool) -> IMap k a -> IMap k a
308filterWithKey f = IMap . adapt_m (IntMap.filterWithKey $ f . coerce) 318filterWithKey f = IMap . adapt_m (IntMap.filterWithKey $ f . coerce)
309 319
310partition :: Coercible (IntMap a,IntMap a) (IMap k a,IMap k a) 320partition :: (a -> Bool) -> IMap k a -> (IMap k a, IMap k a)
311 => (a -> Bool) -> IMap k a -> (IMap k a, IMap k a)
312partition f m = coerce $ IntMap.partition f (intmap m) 321partition f m = coerce $ IntMap.partition f (intmap m)
313 322
314 323
315partitionWithKey :: ( Coercible Int k 324partitionWithKey :: Coercible Int k
316 , Coercible (IntMap a,IntMap a) (IMap k a,IMap k a) )
317 => (k -> a -> Bool) -> IMap k a -> (IMap k a, IMap k a) 325 => (k -> a -> Bool) -> IMap k a -> (IMap k a, IMap k a)
318partitionWithKey f m = coerce $ IntMap.partitionWithKey (f . coerce) (intmap m) 326partitionWithKey f m = coerce $ IntMap.partitionWithKey (f . coerce) (intmap m)
319 327