Skip to content

Commit 63ec59a

Browse files
authored
Use MathJax format for complexity annotations (#411)
Use MathJax format for complexity annotations.
1 parent 68a2945 commit 63ec59a

File tree

7 files changed

+114
-114
lines changed

7 files changed

+114
-114
lines changed

Data/HashMap/Internal.hs

+57-57
Large diffs are not rendered by default.

Data/HashMap/Internal/Array.hs

+8-8
Original file line numberDiff line numberDiff line change
@@ -307,13 +307,13 @@ trim :: MArray s a -> Int -> ST s (Array a)
307307
trim mary n = cloneM mary 0 n >>= unsafeFreeze
308308
{-# INLINE trim #-}
309309

310-
-- | /O(n)/ Insert an element at the given position in this array,
310+
-- | \(O(n)\) Insert an element at the given position in this array,
311311
-- increasing its size by one.
312312
insert :: Array e -> Int -> e -> Array e
313313
insert ary idx b = runST (insertM ary idx b)
314314
{-# INLINE insert #-}
315315

316-
-- | /O(n)/ Insert an element at the given position in this array,
316+
-- | \(O(n)\) Insert an element at the given position in this array,
317317
-- increasing its size by one.
318318
insertM :: Array e -> Int -> e -> ST s (Array e)
319319
insertM ary idx b =
@@ -325,12 +325,12 @@ insertM ary idx b =
325325
where !count = length ary
326326
{-# INLINE insertM #-}
327327

328-
-- | /O(n)/ Update the element at the given position in this array.
328+
-- | \(O(n)\) Update the element at the given position in this array.
329329
update :: Array e -> Int -> e -> Array e
330330
update ary idx b = runST (updateM ary idx b)
331331
{-# INLINE update #-}
332332

333-
-- | /O(n)/ Update the element at the given position in this array.
333+
-- | \(O(n)\) Update the element at the given position in this array.
334334
updateM :: Array e -> Int -> e -> ST s (Array e)
335335
updateM ary idx b =
336336
CHECK_BOUNDS("updateM", count, idx)
@@ -340,7 +340,7 @@ updateM ary idx b =
340340
where !count = length ary
341341
{-# INLINE updateM #-}
342342

343-
-- | /O(n)/ Update the element at the given positio in this array, by
343+
-- | \(O(n)\) Update the element at the given positio in this array, by
344344
-- applying a function to it. Evaluates the element to WHNF before
345345
-- inserting it into the array.
346346
updateWith' :: Array e -> Int -> (e -> e) -> Array e
@@ -349,7 +349,7 @@ updateWith' ary idx f
349349
= update ary idx $! f x
350350
{-# INLINE updateWith' #-}
351351

352-
-- | /O(1)/ Update the element at the given position in this array,
352+
-- | \(O(1)\) Update the element at the given position in this array,
353353
-- without copying.
354354
unsafeUpdateM :: Array e -> Int -> e -> ST s ()
355355
unsafeUpdateM ary idx b =
@@ -428,13 +428,13 @@ thaw !ary !_o@(I# o#) _n@(I# n#) =
428428
(# s2, mary# #) -> (# s2, MArray mary# #)
429429
{-# INLINE thaw #-}
430430

431-
-- | /O(n)/ Delete an element at the given position in this array,
431+
-- | \(O(n)\) Delete an element at the given position in this array,
432432
-- decreasing its size by one.
433433
delete :: Array e -> Int -> Array e
434434
delete ary idx = runST (deleteM ary idx)
435435
{-# INLINE delete #-}
436436

437-
-- | /O(n)/ Delete an element at the given position in this array,
437+
-- | \(O(n)\) Delete an element at the given position in this array,
438438
-- decreasing its size by one.
439439
deleteM :: Array e -> Int -> ST s (Array e)
440440
deleteM ary idx = do

Data/HashMap/Internal/Strict.hs

+21-21
Original file line numberDiff line numberDiff line change
@@ -38,7 +38,7 @@
3838
-- especially when key comparison is expensive, as in the case of
3939
-- strings.
4040
--
41-
-- Many operations have a average-case complexity of /O(log n)/. The
41+
-- Many operations have a average-case complexity of \(O(\log n)\). The
4242
-- implementation uses a large base (i.e. 32) so in practice these
4343
-- operations are constant time.
4444
module Data.HashMap.Internal.Strict
@@ -164,21 +164,21 @@ values are exempted.
164164
------------------------------------------------------------------------
165165
-- * Construction
166166

167-
-- | /O(1)/ Construct a map with a single element.
167+
-- | \(O(1)\) Construct a map with a single element.
168168
singleton :: (Hashable k) => k -> v -> HashMap k v
169169
singleton k !v = HM.singleton k v
170170

171171
------------------------------------------------------------------------
172172
-- * Basic interface
173173

174-
-- | /O(log n)/ Associate the specified value with the specified
174+
-- | \(O(\log n)\) Associate the specified value with the specified
175175
-- key in this map. If this map previously contained a mapping for
176176
-- the key, the old value is replaced.
177177
insert :: (Eq k, Hashable k) => k -> v -> HashMap k v -> HashMap k v
178178
insert k !v = HM.insert k v
179179
{-# INLINABLE insert #-}
180180

181-
-- | /O(log n)/ Associate the value with the key in this map. If
181+
-- | \(O(\log n)\) Associate the value with the key in this map. If
182182
-- this map previously contained a mapping for the key, the old value
183183
-- is replaced by the result of applying the given function to the new
184184
-- and old value. Example:
@@ -259,7 +259,7 @@ unsafeInsertWithKey f k0 v0 m0 = runST (go h0 k0 v0 0 m0)
259259
| otherwise = go h k x s $ BitmapIndexed (mask hy s) (A.singleton t)
260260
{-# INLINABLE unsafeInsertWithKey #-}
261261

262-
-- | /O(log n)/ Adjust the value tied to a given key in this map only
262+
-- | \(O(\log n)\) Adjust the value tied to a given key in this map only
263263
-- if it is present. Otherwise, leave the map alone.
264264
adjust :: (Eq k, Hashable k) => (v -> v) -> k -> HashMap k v -> HashMap k v
265265
adjust f k0 m0 = go h0 k0 0 m0
@@ -288,14 +288,14 @@ adjust f k0 m0 = go h0 k0 0 m0
288288
| otherwise = t
289289
{-# INLINABLE adjust #-}
290290

291-
-- | /O(log n)/ The expression @('update' f k map)@ updates the value @x@ at @k@
291+
-- | \(O(\log n)\) The expression @('update' f k map)@ updates the value @x@ at @k@
292292
-- (if it is in the map). If @(f x)@ is 'Nothing', the element is deleted.
293293
-- If it is @('Just' y)@, the key @k@ is bound to the new value @y@.
294294
update :: (Eq k, Hashable k) => (a -> Maybe a) -> k -> HashMap k a -> HashMap k a
295295
update f = alter (>>= f)
296296
{-# INLINABLE update #-}
297297

298-
-- | /O(log n)/ The expression @('alter' f k map)@ alters the value @x@ at @k@, or
298+
-- | \(O(\log n)\) The expression @('alter' f k map)@ alters the value @x@ at @k@, or
299299
-- absence thereof.
300300
--
301301
-- 'alter' can be used to insert, delete, or update a value in a map. In short:
@@ -310,7 +310,7 @@ alter f k m =
310310
Just v -> insert k v m
311311
{-# INLINABLE alter #-}
312312

313-
-- | /O(log n)/ The expression (@'alterF' f k map@) alters the value @x@ at
313+
-- | \(O(\log n)\) The expression (@'alterF' f k map@) alters the value @x@ at
314314
-- @k@, or absence thereof.
315315
--
316316
-- 'alterF' can be used to insert, delete, or update a value in a map.
@@ -436,14 +436,14 @@ alterFEager f !k !m = (<$> f mv) $ \fres ->
436436
------------------------------------------------------------------------
437437
-- * Combine
438438

439-
-- | /O(n+m)/ The union of two maps. If a key occurs in both maps,
439+
-- | \(O(n+m)\) The union of two maps. If a key occurs in both maps,
440440
-- the provided function (first argument) will be used to compute the result.
441441
unionWith :: (Eq k, Hashable k) => (v -> v -> v) -> HashMap k v -> HashMap k v
442442
-> HashMap k v
443443
unionWith f = unionWithKey (const f)
444444
{-# INLINE unionWith #-}
445445

446-
-- | /O(n+m)/ The union of two maps. If a key occurs in both maps,
446+
-- | \(O(n+m)\) The union of two maps. If a key occurs in both maps,
447447
-- the provided function (first argument) will be used to compute the result.
448448
unionWithKey :: (Eq k, Hashable k) => (k -> v -> v -> v) -> HashMap k v -> HashMap k v
449449
-> HashMap k v
@@ -532,7 +532,7 @@ unionWithKey f = go 0
532532
------------------------------------------------------------------------
533533
-- * Transformations
534534

535-
-- | /O(n)/ Transform this map by applying a function to every value.
535+
-- | \(O(n)\) Transform this map by applying a function to every value.
536536
mapWithKey :: (k -> v1 -> v2) -> HashMap k v1 -> HashMap k v2
537537
mapWithKey f = go
538538
where
@@ -544,7 +544,7 @@ mapWithKey f = go
544544
Collision h $ A.map' (\ (L k v) -> let !v' = f k v in L k v') ary
545545
{-# INLINE mapWithKey #-}
546546

547-
-- | /O(n)/ Transform this map by applying a function to every value.
547+
-- | \(O(n)\) Transform this map by applying a function to every value.
548548
map :: (v1 -> v2) -> HashMap k v1 -> HashMap k v2
549549
map f = mapWithKey (const f)
550550
{-# INLINE map #-}
@@ -553,7 +553,7 @@ map f = mapWithKey (const f)
553553
------------------------------------------------------------------------
554554
-- * Filter
555555

556-
-- | /O(n)/ Transform this map by applying a function to every value
556+
-- | \(O(n)\) Transform this map by applying a function to every value
557557
-- and retaining only some of them.
558558
mapMaybeWithKey :: (k -> v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
559559
mapMaybeWithKey f = HM.filterMapAux onLeaf onColl
@@ -564,13 +564,13 @@ mapMaybeWithKey f = HM.filterMapAux onLeaf onColl
564564
| otherwise = Nothing
565565
{-# INLINE mapMaybeWithKey #-}
566566

567-
-- | /O(n)/ Transform this map by applying a function to every value
567+
-- | \(O(n)\) Transform this map by applying a function to every value
568568
-- and retaining only some of them.
569569
mapMaybe :: (v1 -> Maybe v2) -> HashMap k v1 -> HashMap k v2
570570
mapMaybe f = mapMaybeWithKey (const f)
571571
{-# INLINE mapMaybe #-}
572572

573-
-- | /O(n)/ Perform an 'Applicative' action for each key-value pair
573+
-- | \(O(n)\) Perform an 'Applicative' action for each key-value pair
574574
-- in a 'HashMap' and produce a 'HashMap' of all the results. Each 'HashMap'
575575
-- will be strict in all its values.
576576
--
@@ -599,7 +599,7 @@ traverseWithKey f = go
599599
------------------------------------------------------------------------
600600
-- * Difference and intersection
601601

602-
-- | /O(n*log m)/ Difference with a combining function. When two equal keys are
602+
-- | \(O(n \log m)\) Difference with a combining function. When two equal keys are
603603
-- encountered, the combining function is applied to the values of these keys.
604604
-- If it returns 'Nothing', the element is discarded (proper set difference). If
605605
-- it returns (@'Just' y@), the element is updated with a new value @y@.
@@ -611,7 +611,7 @@ differenceWith f a b = HM.foldlWithKey' go HM.empty a
611611
Just w -> maybe m (\ !y -> HM.unsafeInsert k y m) (f v w)
612612
{-# INLINABLE differenceWith #-}
613613

614-
-- | /O(n+m)/ Intersection of two maps. If a key occurs in both maps
614+
-- | \(O(n+m)\) Intersection of two maps. If a key occurs in both maps
615615
-- the provided function is used to combine the values from the two
616616
-- maps.
617617
intersectionWith :: (Eq k, Hashable k) => (v1 -> v2 -> v3) -> HashMap k v1
@@ -623,7 +623,7 @@ intersectionWith f a b = HM.foldlWithKey' go HM.empty a
623623
_ -> m
624624
{-# INLINABLE intersectionWith #-}
625625

626-
-- | /O(n+m)/ Intersection of two maps. If a key occurs in both maps
626+
-- | \(O(n+m)\) Intersection of two maps. If a key occurs in both maps
627627
-- the provided function is used to combine the values from the two
628628
-- maps.
629629
intersectionWithKey :: (Eq k, Hashable k) => (k -> v1 -> v2 -> v3)
@@ -638,14 +638,14 @@ intersectionWithKey f a b = HM.foldlWithKey' go HM.empty a
638638
------------------------------------------------------------------------
639639
-- ** Lists
640640

641-
-- | /O(n*log n)/ Construct a map with the supplied mappings. If the
641+
-- | \(O(n \log n)\) Construct a map with the supplied mappings. If the
642642
-- list contains duplicate mappings, the later mappings take
643643
-- precedence.
644644
fromList :: (Eq k, Hashable k) => [(k, v)] -> HashMap k v
645645
fromList = List.foldl' (\ m (k, !v) -> HM.unsafeInsert k v m) HM.empty
646646
{-# INLINABLE fromList #-}
647647

648-
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
648+
-- | \(O(n \log n)\) Construct a map from a list of elements. Uses
649649
-- the provided function @f@ to merge duplicate entries with
650650
-- @(f newVal oldVal)@.
651651
--
@@ -679,7 +679,7 @@ fromListWith :: (Eq k, Hashable k) => (v -> v -> v) -> [(k, v)] -> HashMap k v
679679
fromListWith f = List.foldl' (\ m (k, v) -> unsafeInsertWith f k v m) HM.empty
680680
{-# INLINE fromListWith #-}
681681

682-
-- | /O(n*log n)/ Construct a map from a list of elements. Uses
682+
-- | \(O(n \log n)\) Construct a map from a list of elements. Uses
683683
-- the provided function to merge duplicate entries.
684684
--
685685
-- === Examples

Data/HashMap/Lazy.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -19,7 +19,7 @@
1919
-- especially when key comparison is expensive, as in the case of
2020
-- strings.
2121
--
22-
-- Many operations have a average-case complexity of /O(log n)/. The
22+
-- Many operations have a average-case complexity of \(O(\log n)\). The
2323
-- implementation uses a large base (i.e. 32) so in practice these
2424
-- operations are constant time.
2525
module Data.HashMap.Lazy

Data/HashMap/Strict.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -18,7 +18,7 @@
1818
-- especially when key comparison is expensive, as in the case of
1919
-- strings.
2020
--
21-
-- Many operations have a average-case complexity of /O(log n)/. The
21+
-- Many operations have a average-case complexity of \(O(\log n)\). The
2222
-- implementation uses a large base (i.e. 16) so in practice these
2323
-- operations are constant time.
2424
module Data.HashMap.Strict

Data/HashSet.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -86,7 +86,7 @@ The implementation is based on /hash array mapped tries/. A
8686
especially when value comparisons are expensive, as in the case of
8787
strings.
8888
89-
Many operations have a average-case complexity of /O(log n)/. The
89+
Many operations have a average-case complexity of \(O(\log n)\). The
9090
implementation uses a large base (i.e. 16) so in practice these
9191
operations are constant time.
9292
-}

0 commit comments

Comments
 (0)