summaryrefslogtreecommitdiff
path: root/lib
diff options
context:
space:
mode:
authorAndrew Cady <d@jerkface.net>2019-07-13 16:00:49 -0400
committerAndrew Cady <d@jerkface.net>2019-07-13 16:00:49 -0400
commit803d8a03e5c787d1d57b327cbc30a5beb9f1ec7a (patch)
tree7b0bb79eae3af88db6db47f22cdd10d12934e8b2 /lib
parent9a7c8195e5330c868b0e2b9b25af915d5fd2bd7a (diff)
make unused code compile
Diffstat (limited to 'lib')
-rw-r--r--lib/IntMapClass.hs324
1 files changed, 324 insertions, 0 deletions
diff --git a/lib/IntMapClass.hs b/lib/IntMapClass.hs
new file mode 100644
index 0000000..c5e6a88
--- /dev/null
+++ b/lib/IntMapClass.hs
@@ -0,0 +1,324 @@
1{-# LANGUAGE CPP,
2 FlexibleContexts,
3 MultiParamTypeClasses,
4 GeneralizedNewtypeDeriving,
5 DeriveTraversable,
6 DeriveDataTypeable #-}
7module IntMapClass where
8
9import qualified Data.IntMap.Strict as IntMap
10import Data.IntMap.Strict ( IntMap )
11import Data.Typeable ( Typeable )
12import Data.Data ( Data )
13import Data.Foldable ( Foldable )
14import Data.Traversable ( Traversable )
15import Data.Monoid ( Monoid )
16import Control.DeepSeq ( NFData )
17import Control.Applicative ( Applicative )
18import Data.Coerce
19
20newtype IMap k a = IMap { intmap :: IntMap a }
21 deriving
22 ( Functor
23 , Typeable
24 , Foldable
25 , Traversable
26 , Eq
27 , Data
28 , Ord
29 , Read
30 , Show
31 , Semigroup
32 , Monoid
33 , NFData
34 )
35
36adaptm_k_a_m f k a m = IMap $ adapt_k_a_m f k a m
37adapt_k_a_m f k a m = adapt_m (adapt_k f k a) m
38
39adapt_m_k :: Coercible k Int => (IntMap a -> Int -> x) -> IMap k a -> k -> x
40adapt_m_k f (IMap m) k = f m (coerce k)
41
42adapt_k_m :: Coercible k Int => (Int -> IntMap a -> x) -> k -> IMap k a -> x
43adapt_k_m f k (IMap m) = f (coerce k) m
44-- adapt_k_m2 :: Coercible k Int => (Int -> IntMap a -> x) -> k -> IMap k a -> x
45-- adapt_k_m2 f k m = (adapt_k f) k (intmap m)
46
47adaptm_k_m
48 :: Coercible k Int =>
49 (Int -> IntMap a -> IntMap a) -> k -> IMap k a -> IMap k a
50adaptm_k_m f k m = IMap $ adapt_k_m f k m
51
52adapt_k :: Coercible k Int => (Int -> x) -> k -> x
53adapt_k f k = f (coerce k)
54
55adapt_m_m :: (IntMap a -> IntMap a -> x) -> IMap k a -> IMap k a -> x
56adapt_m_m f m = adapt_m (adapt_m f m)
57
58adaptm_m_m :: (IntMap a -> IntMap a -> IntMap a) -> IMap k a -> IMap k a -> IMap k a
59adaptm_m_m f a b = IMap $ adapt_m_m f a b
60
61adapt_m :: (IntMap a -> x) -> IMap k a -> x
62adapt_m f (IMap m) = f m
63
64first f (x,y) = (f x,y)
65second f (x,y) = (x,f y)
66
67
68(!) :: Coercible k Int => IMap k a -> k -> a
69(!) = adapt_m_k (IntMap.!)
70
71(\\) :: IMap k a -> IMap k a -> IMap k a
72(\\) a b = IMap $ adapt_m_m (IntMap.\\) a b
73
74null = adapt_m (IntMap.null)
75size = adapt_m (IntMap.size)
76
77member :: Coercible k Int => k -> IMap k a -> Bool
78member = adapt_k_m (IntMap.member)
79
80notMember :: Coercible k Int => k -> IMap k a -> Bool
81notMember = adapt_k_m (IntMap.notMember)
82
83lookup :: Coercible k Int => k -> IMap k a -> Maybe a
84lookup = adapt_k_m (IntMap.lookup)
85
86findWithDefault :: Coercible k Int => x -> k -> IMap k x -> x
87findWithDefault a = adapt_k_m (IntMap.findWithDefault a)
88
89-- FIXME: fmap (first coerce) probably incurs cost
90lookupLT :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a)
91lookupLT k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupLT) k m
92lookupGT :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a)
93lookupGT k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupGT) k m
94lookupLE :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a)
95lookupLE k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupLE) k m
96lookupGE :: ( Coercible Int k, Coercible k Int ) => k -> IMap k a -> Maybe (k, a)
97lookupGE k m = fmap (first coerce) $ adapt_k_m (IntMap.lookupGE) k m
98
99empty = IMap IntMap.empty
100
101singleton :: Coercible k Int => k -> a -> IMap k a
102singleton = (IMap .) . adapt_k IntMap.singleton
103
104insert :: Coercible k Int => k -> a -> IMap k a -> IMap k a
105insert = adaptm_k_a_m IntMap.insert
106
107insertWith :: Coercible k Int => (a -> a -> a) -> k -> a -> IMap k a -> IMap k a
108insertWith f = adaptm_k_a_m (IntMap.insertWith f)
109
110insertWithKey :: (Coercible Int k, Coercible k Int) => (k -> a -> a -> a) -> k -> a -> IMap k a -> IMap k a
111insertWithKey f = adaptm_k_a_m (IntMap.insertWithKey $ f . coerce)
112
113insertLookupWithKey :: (Coercible Int k, Coercible k Int) =>
114 (k -> a -> a -> a) -> k -> a -> IMap k a -> (Maybe a, IMap k a)
115insertLookupWithKey f k a m = second IMap $ adapt_k_a_m (IntMap.insertLookupWithKey $ f . coerce) k a m
116
117delete :: Coercible k Int => k -> IMap k a -> IMap k a
118delete = adaptm_k_m IntMap.delete
119
120adjust :: Coercible k Int => (a -> a) -> k -> IMap k a -> IMap k a
121adjust f = adaptm_k_m (IntMap.adjust f)
122
123adjustWithKey :: ( Coercible Int k, Coercible k Int ) =>
124 (k -> a -> a) -> k -> IMap k a -> IMap k a
125adjustWithKey f = adaptm_k_m (IntMap.adjustWithKey $ f . coerce)
126
127update
128 :: Coercible k Int => (a -> Maybe a) -> k -> IMap k a -> IMap k a
129update f = adaptm_k_m (IntMap.update f)
130
131
132updateWithKey
133 :: (Coercible k Int, Coercible Int k) =>
134 (k -> a -> Maybe a) -> k -> IMap k a -> IMap k a
135updateWithKey f = adaptm_k_m (IntMap.updateWithKey $ f . coerce)
136
137updateLookupWithKey ::
138 (Coercible k Int, Coercible Int k) =>
139 (k -> a -> Maybe a) -> k -> IMap k a -> (Maybe a, IMap k a)
140updateLookupWithKey f k m =
141 second IMap $ adapt_k_m (IntMap.updateLookupWithKey $ f . coerce) k m
142
143alter :: Coercible k Int => (Maybe a -> Maybe a) -> k -> IMap k a -> IMap k a
144alter f = adaptm_k_m (IntMap.alter f)
145
146union :: IMap k a -> IMap k a -> IMap k a
147union = adaptm_m_m IntMap.union
148
149unionWith :: (a -> a -> a) -> IMap k a -> IMap k a -> IMap k a
150unionWith f = adaptm_m_m (IntMap.unionWith f)
151
152
153unionWithKey :: Coercible Int k => (k -> a -> a -> a) -> IMap k a -> IMap k a -> IMap k a
154unionWithKey f = adaptm_m_m (IntMap.unionWithKey $ f . coerce)
155
156-- unions :: Coercible [IMap k a] [IntMap a] => [IMap k a] -> IMap k a
157-- unions ms = IMap $ IntMap.unions (coerce ms)
158
159-- unionsWith :: Coercible [IMap k a] [IntMap a] => (a->a->a) -> [IMap k a] -> IMap k a
160-- unionsWith f ms = IMap $ IntMap.unionsWith f (coerce ms)
161
162difference = adaptm_m_m IntMap.difference
163
164differenceWith f = adaptm_m_m (IntMap.differenceWith f)
165
166differenceWithKey ::
167 Coercible Int k =>
168 (k -> a -> a -> Maybe a) -> IMap k a -> IMap k a -> IMap k a
169differenceWithKey f = adaptm_m_m (IntMap.differenceWithKey $ f . coerce)
170
171intersection = adaptm_m_m IntMap.intersection
172intersectionWith f = adaptm_m_m (IntMap.intersectionWith f)
173
174mergeWithKey ::
175 Coercible Int k =>
176 (k -> a -> b -> Maybe c)
177 -> (IMap k a -> IMap k c)
178 -> (IMap k b -> IMap k c)
179 -> IMap k a
180 -> IMap k b
181 -> IMap k c
182mergeWithKey f g1 g2 = adaptm_m_m (IntMap.mergeWithKey f' g1' g2')
183 where f' = f . coerce
184 g1' = intmap . g1 . IMap
185 g2' = intmap . g2 . IMap
186 adapt_m_m f m = adapt_m (adapt_m f m)
187 adaptm_m_m f a b = IMap $ adapt_m_m f a b
188
189map :: (a -> b) -> IMap k a -> IMap k b
190map f = IMap . adapt_m (IntMap.map f)
191
192mapWithKey :: Coercible Int k => (k -> a -> b) -> IMap k a -> IMap k b
193mapWithKey f = IMap . adapt_m (IntMap.mapWithKey $ f . coerce)
194
195-- FIXME: fmap IMap ?
196traverseWithKey ::
197 (Applicative f, Coercible Int k) =>
198 (k -> a -> f b) -> IMap k a -> f (IMap k b)
199traverseWithKey f = fmap IMap . adapt_m (IntMap.traverseWithKey $ f . coerce)
200
201mapAccum :: (t -> b -> (t, a)) -> t -> IMap k b -> (t, IMap k a)
202mapAccum f a m = second IMap $ IntMap.mapAccum f a (intmap m)
203
204mapAccumWithKey :: Coercible Int k =>
205 (t -> k -> b -> (t, a)) -> t -> IMap k b -> (t, IMap k a)
206mapAccumWithKey f a m = second IMap $ IntMap.mapAccumWithKey f' a (intmap m)
207 where f' a k b = f a (coerce k) b
208
209
210mapAccumRWithKey :: Coercible Int k =>
211 (t -> k -> b -> (t, a)) -> t -> IMap k b -> (t, IMap k a)
212mapAccumRWithKey f a m = second IMap $ IntMap.mapAccumRWithKey f' a (intmap m)
213 where f' a k b = f a (coerce k) b
214
215mapKeys :: (Coercible Int k1, Coercible k2 Int) =>
216 (k1 -> k2) -> IMap k1 a -> IMap k2 a
217mapKeys f = IMap . adapt_m (IntMap.mapKeys (coerce . f . coerce))
218
219mapKeysWith :: (Coercible Int k1, Coercible k2 Int) =>
220 (a->a->a) -> (k1 -> k2) -> IMap k1 a -> IMap k2 a
221mapKeysWith c f = IMap . adapt_m (IntMap.mapKeysWith c (coerce . f . coerce))
222
223mapKeysMonotonic :: (Coercible Int k1, Coercible k2 Int) =>
224 (k1 -> k2) -> IMap k1 a -> IMap k2 a
225mapKeysMonotonic f = IMap . adapt_m (IntMap.mapKeysMonotonic (coerce . f . coerce))
226
227foldr :: (a -> x -> x) -> x -> IMap k a -> x
228foldr f b = adapt_m (IntMap.foldr f b)
229
230foldl :: (x -> a -> x) -> x -> IMap k a -> x
231foldl f a = adapt_m (IntMap.foldl f a)
232
233foldrWithKey :: Coercible Int b => (b -> a -> x -> x) -> x -> IMap k a -> x
234foldrWithKey f b = adapt_m (IntMap.foldrWithKey (f . coerce) b)
235
236foldlWithKey ::
237 Coercible Int k => (x -> k -> a -> x) -> x -> IMap k a -> x
238foldlWithKey f a = adapt_m (IntMap.foldlWithKey f' a) where f' a = f a . coerce
239
240foldMapWithKey :: (Monoid m, Coercible k Int) => (k -> a -> m) -> IMap k a -> m
241foldMapWithKey f = adapt_m (IntMap.foldMapWithKey $ f . coerce)
242
243foldr' :: (a -> x -> x) -> x -> IMap k a -> x
244foldr' f b = adapt_m (IntMap.foldr' f b)
245
246foldl' :: (a -> x -> a) -> a -> IMap k x -> a
247foldl' f b = adapt_m (IntMap.foldl' f b)
248
249foldrWithKey' :: Coercible Int b => (b -> a -> x -> x) -> x -> IMap k a -> x
250foldrWithKey' f b = adapt_m (IntMap.foldrWithKey' (f . coerce) b)
251
252foldlWithKey' ::
253 Coercible Int k => (x -> k -> a -> x) -> x -> IMap k a -> x
254foldlWithKey' f a = adapt_m (IntMap.foldlWithKey' f' a) where f' a = f a . coerce
255
256elems :: IMap k a -> [a]
257elems = IntMap.elems . intmap
258
259keys :: Coercible [Int] [k] => IMap k a -> [k]
260keys = coerce . IntMap.keys . intmap
261
262assocs :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k, a)]
263assocs = coerce . IntMap.assocs . intmap
264
265-- Not implementing... (doing it right requires wrapping IntSet)
266-- keysSet :: IntMap a -> IntSet
267-- fromSet :: (Key -> a) -> IntSet -> IntMap a
268
269toList :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k, a)]
270toList = coerce . IntMap.toList . intmap
271
272fromList :: Coercible [(k,a)] [(Int,a)] => [(k, a)] -> IMap k a
273fromList = IMap . IntMap.fromList . coerce
274
275fromListWith :: Coercible [(k,a)] [(Int,a)] => (a -> a -> a) -> [(k, a)] -> IMap k a
276fromListWith f = IMap . IntMap.fromListWith f . coerce
277
278fromListWithKey :: ( Coercible Int k
279 , Coercible [(k,a)] [(Int,a)] ) =>
280 (k -> a -> a -> a) -> [(k, a)] -> IMap k a
281fromListWithKey f = IMap . IntMap.fromListWithKey (f . coerce) . coerce
282
283toAscList :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k,a)]
284toAscList (IMap m) = coerce $ IntMap.toAscList m
285
286toDescList :: Coercible [(Int,a)] [(k,a)] => IMap k a -> [(k,a)]
287toDescList (IMap m) = coerce $ IntMap.toDescList m
288
289fromAscList :: Coercible [(k,a)] [(Int,a)] => [(k, a)] -> IMap k a
290fromAscList = IMap . IntMap.fromAscList . coerce
291
292fromAscListWith ::
293 Coercible [(k,a)] [(Int, a)] =>
294 (a -> a -> a) -> [(k,a)] -> IMap k a
295fromAscListWith f = IMap . IntMap.fromAscListWith f . coerce
296
297fromAscListWithKey ::
298 (Coercible Int k, Coercible [(k,a)] [(Int, a)]) =>
299 (k -> a -> a -> a) -> [(k,a)] -> IMap k a
300fromAscListWithKey f = IMap . IntMap.fromAscListWithKey (f . coerce) . coerce
301
302fromDistinctAscList :: Coercible [(k,a)] [(Int,a)] => [(k, a)] -> IMap k a
303fromDistinctAscList = IMap . IntMap.fromDistinctAscList . coerce
304
305filter :: (a -> Bool) -> IMap k a -> IMap k a
306filter f = IMap . adapt_m (IntMap.filter f)
307
308filterWithKey :: Coercible Int k => (k -> a -> Bool) -> IMap k a -> IMap k a
309filterWithKey f = IMap . adapt_m (IntMap.filterWithKey $ f . coerce)
310
311partition :: Coercible (IntMap a,IntMap a) (IMap k a,IMap k a)
312 => (a -> Bool) -> IMap k a -> (IMap k a, IMap k a)
313partition f m = coerce $ IntMap.partition f (intmap m)
314
315
316partitionWithKey :: ( Coercible Int k
317 , Coercible (IntMap a,IntMap a) (IMap k a,IMap k a) )
318 => (k -> a -> Bool) -> IMap k a -> (IMap k a, IMap k a)
319partitionWithKey f m = coerce $ IntMap.partitionWithKey (f . coerce) (intmap m)
320
321mapMaybe :: (a -> Maybe b) -> IMap k a -> IMap k b
322mapMaybe f = IMap . IntMap.mapMaybe f . intmap
323
324