Skip to content

Commit 82a1867

Browse files
committed
[BRAKING] fix: user function of Bisect.maxRight to take [l, i) (#140)
1 parent 9d6eed1 commit 82a1867

File tree

5 files changed

+40
-68
lines changed

5 files changed

+40
-68
lines changed

src/AtCoder/Extra/Bisect.hs

Lines changed: 31 additions & 62 deletions
Original file line numberDiff line numberDiff line change
@@ -2,9 +2,6 @@
22

33
-- | Bisection methods and binary search functions.
44
--
5-
-- __Known bug__: `maxRight` and their variants have a bug ([#140](https://github.com/toyboot4e/ac-library-hs/issues/140)),
6-
-- so don't use them.
7-
--
85
-- ==== __Example__
96
-- Perform index compression with `lowerBound`:
107
--
@@ -25,10 +22,6 @@ module AtCoder.Extra.Bisect
2522
upperBoundIn,
2623

2724
-- * Generic bisection methods
28-
29-
--
30-
-- __Known bug_:_ `maxRight` and their variants have a bug ([#140](https://github.com/toyboot4e/ac-library-hs/issues/140)),
31-
-- so don't use them.
3225
maxRight,
3326
maxRightM,
3427
minLeft,
@@ -41,13 +34,8 @@ import Data.Functor.Identity
4134
import Data.Vector.Generic qualified as VG
4235
import GHC.Stack (HasCallStack)
4336

44-
-- | \(O(\log n)\) Returns the maximum \(r\) where \(x_i \lt x_{ref}\) holds for \(i \in [0, r)\).
45-
--
46-
-- @
47-
-- Y Y Y Y Y N N N N N Y: x_i < x_ref
48-
-- --------- *---------> x N: not Y
49-
-- R R: the right boundary point returned
50-
-- @
37+
-- | \(O(\log n)\) Returns the maximum \(r_{\mathrm{max}}\) where \(x_i \lt x_{r_{\mathrm{max}}}\)
38+
-- holds for \(i \in [0, r_{\mathrm{max}})\).
5139
--
5240
-- ==== __Example__
5341
-- >>> import Data.Vector.Unboxed qualified as VU
@@ -72,7 +60,8 @@ import GHC.Stack (HasCallStack)
7260
lowerBound :: (HasCallStack, VG.Vector v a, Ord a) => v a -> a -> Int
7361
lowerBound vec = lowerBoundIn 0 (VG.length vec) vec
7462

75-
-- | \(O(\log n)\) Computes the `lowerBound` for a slice of a vector within the interval \([l, r)\).
63+
-- | \(O(\log n)\) Returns the maximum \(r_{\mathrm{max}}\) where \(x_i \lt x_{r_{\mathrm{max}}}\)
64+
-- holds for \(i \in [l, r_{\mathrm{max}})\) ( \(r_{\mathrm{max}} \le r\) ).
7665
--
7766
-- ==== Constraints
7867
-- - \(0 \le l \le r \le n\)
@@ -99,17 +88,12 @@ lowerBound vec = lowerBoundIn 0 (VG.length vec) vec
9988
-- @since 1.3.0.0
10089
{-# INLINE lowerBoundIn #-}
10190
lowerBoundIn :: (HasCallStack, VG.Vector v a, Ord a) => Int -> Int -> v a -> a -> Int
102-
lowerBoundIn l r vec target = maxRight l r $ \i -> vec VG.! i < target
91+
lowerBoundIn l r vec target = maxRight l r $ \i -> vec VG.! (i - 1) < target
10392
where
10493
!_ = ACIA.checkIntervalBounded "AtCoder.Extra.Bisect.lowerBoundIn" l r $ VG.length vec
10594

106-
-- | \(O(\log n)\) Returns the maximum \(r\) where \(x_i \le x_{ref}\) holds for \(i \in [0, r)\).
107-
--
108-
-- @
109-
-- Y Y Y Y Y N N N N N Y: x_i <= x_ref
110-
-- --------- *---------> x N: not Y
111-
-- R R: the right boundary point returned
112-
-- @
95+
-- | \(O(\log n)\) Returns the maximum \(r_{\mathrm{max}}\) where \(x_i \le x_{r_{\mathrm{max}}}\)
96+
-- holds for \(i \in [0, r_{\mathrm{max}})\).
11397
--
11498
-- ==== __Example__
11599
-- >>> import Data.Vector.Unboxed qualified as VU
@@ -137,7 +121,8 @@ lowerBoundIn l r vec target = maxRight l r $ \i -> vec VG.! i < target
137121
upperBound :: (HasCallStack, VG.Vector v a, Ord a) => v a -> a -> Int
138122
upperBound vec = upperBoundIn 0 (VG.length vec) vec
139123

140-
-- | \(O(\log n)\) Computes the `upperBound` for a slice of a vector within the interval \([l, r)\).
124+
-- | \(O(\log n)\) Returns the maximum \(r_{\mathrm{max}}\) where \(x_i \le x_{r_{\mathrm{max}}}\)
125+
-- holds for \(i \in [l, r_{\mathrm{max}})\) ( \(r_{\mathrm{max}} \le r\) ).
141126
--
142127
-- ==== Constraints
143128
-- - \(0 \le l \le r \le n\)
@@ -167,35 +152,28 @@ upperBound vec = upperBoundIn 0 (VG.length vec) vec
167152
-- @since 1.3.0.0
168153
{-# INLINE upperBoundIn #-}
169154
upperBoundIn :: (HasCallStack, VG.Vector v a, Ord a) => Int -> Int -> v a -> a -> Int
170-
upperBoundIn l r vec target = maxRight l r $ \i -> vec VG.! i <= target
155+
upperBoundIn l r vec target = maxRight l r $ \i -> vec VG.! (i - 1) <= target
171156
where
172157
!_ = ACIA.checkIntervalBounded "AtCoder.Extra.Bisect.upperBoundIn" l r $ VG.length vec
173158

174159
-- | \(O(\log n)\) Applies the bisection method on a half-open interval \([l, r)\) and returns the
175-
-- right boundary point.
176-
--
177-
-- @
178-
-- Y Y Y Y Y N N N N N Y: p(i) returns `true`
179-
-- --------- *---------> x N: not Y
180-
-- R R: the right boundary point returned
181-
-- @
182-
--
183-
-- __Known bug__: user function \(p\) takes __closed intervals__ \([l, r]\).
160+
-- right boundary point \(r_{\mathrm{max}}\), where \(p[l, i)\) holds for
161+
-- \(i \in [l, r_{\mathrm{max}}]\).
184162
--
185163
-- ==== __Example__
186164
-- >>> import Data.Vector.Unboxed qualified as VU
187165
-- >>> let xs = VU.fromList [10, 10, 20, 20, 30, 30]
188166
-- >>> let n = VU.length xs
189-
-- >>> maxRight 0 n ((<= 20) . (xs VU.!))
167+
-- >>> maxRight 0 n (\i -> xs VU.! (i - 1) <= 20)
190168
-- 4
191169
--
192-
-- >>> maxRight 0 n ((<= 0) . (xs VU.!))
170+
-- >>> maxRight 0 n (\i -> xs VU.! (i - 1) <= 0)
193171
-- 0
194172
--
195-
-- >>> maxRight 0 n ((<= 100) . (xs VU.!))
173+
-- >>> maxRight 0 n (\i -> xs VU.! (i - 1) <= 100)
196174
-- 6
197175
--
198-
-- >>> maxRight 0 3 ((<= 20) . (xs VU.!))
176+
-- >>> maxRight 0 3 (\i -> xs VU.! (i - 1) <= 20)
199177
-- 3
200178
--
201179
-- @since 1.3.0.0
@@ -206,45 +184,37 @@ maxRight ::
206184
Int ->
207185
-- | \(r\)
208186
Int ->
209-
-- | \(p\)
187+
-- | \(p\): user predicate that works on \([l, i)\)
210188
(Int -> Bool) ->
211-
-- | Maximum \(r' (r' \le r)\) where \(p(i)\) holds for \(i \in [l, r')\).
189+
-- | Maximum \(r_{\mathrm{max}} (r_{\mathrm{max}} \le r)\) where \(p[l, i)\) holds for
190+
-- \(i \in [l, r_{\mathrm{max}}]\).
212191
Int
213192
maxRight l r p = runIdentity $ maxRightM l r (pure . p)
214193

215194
-- | \(O(\log n)\) Monadic variant of `maxRight`.
216195
--
217-
-- __Known bug__: user function \(p\) takes __closed intervals__ \([l, r]\).
218-
--
219196
-- @since 1.3.0.0
220197
{-# INLINE maxRightM #-}
221198
maxRightM :: (HasCallStack, Monad m) => Int -> Int -> (Int -> m Bool) -> m Int
222-
maxRightM l0 r0 p = bisectImpl (l0 - 1) r0 p
199+
maxRightM l0 r0 = bisectImpl l0 (r0 + 1)
223200
where
224201
!_ = ACIA.checkInterval "AtCoder.Extra.Bisect.maxRightM" l0 r0
225202

226203
-- | \(O(\log n)\) Applies the bisection method on a half-open interval \([l, r)\) and returns the
227-
-- left boundary point.
228-
--
229-
-- @
230-
-- N N N N N Y Y Y Y Y Y: p(i) returns `true`
231-
-- --------* ----------> x N: not Y
232-
-- L L: the left boundary point returned
233-
-- @
234-
--
235-
-- __Known bug__: user function \(p\) takes __closed intervals__ \([l, r]\).
204+
-- right boundary point \(l_{\mathrm{min}}\), where \(p[i, r)\) holds for
205+
-- \(i \in [l_{\mathrm{min}}, r]\).
236206
--
237207
-- ==== __Example__
238208
-- >>> import Data.Vector.Unboxed qualified as VU
239209
-- >>> let xs = VU.fromList [10, 10, 20, 20, 30, 30]
240210
-- >>> let n = VU.length xs
241-
-- >>> minLeft 0 n ((>= 20) . (xs VU.!))
211+
-- >>> minLeft 0 n (\i -> xs VU.! i >= 20)
242212
-- 2
243213
--
244-
-- >>> minLeft 0 n ((>= 0) . (xs VU.!))
214+
-- >>> minLeft 0 n (\i -> xs VU.! i >= 0)
245215
-- 0
246216
--
247-
-- >>> minLeft 0 n ((>= 100) . (xs VU.!))
217+
-- >>> minLeft 0 n (\i -> xs VU.! i >= 100)
248218
-- 6
249219
--
250220
-- @since 1.3.0.0
@@ -255,30 +225,29 @@ minLeft ::
255225
Int ->
256226
-- | \(r\)
257227
Int ->
258-
-- | \(p\)
228+
-- | \(p\): user predicate that works on \([i, r)\)
259229
(Int -> Bool) ->
260-
-- | Minimum \(l' (l' \ge l)\) where \(p(i)\) holds for \(i \in [l', r)\)
230+
-- | Minimum \(l_{\mathrm{min}}(l_{\mathrm{min}} \ge l)\) where \(p[i, r)\) holds for
231+
-- \(i \in [l_{\mathrm{min}}, r]\)
261232
Int
262233
minLeft l r p = runIdentity $ minLeftM l r (pure . p)
263234

264235
-- | \(O(\log n)\) Monadic variant of `minLeft`.
265236
--
266-
-- __Known bug__: user function \(p\) takes __closed intervals__ \([l, r]\).
267-
--
268237
-- @since 1.3.0.0
269238
{-# INLINE minLeftM #-}
270239
minLeftM :: (HasCallStack, Monad m) => Int -> Int -> (Int -> m Bool) -> m Int
271-
minLeftM l r p = (+ 1) <$> bisectImpl r (l - 1) p
240+
minLeftM l r = bisectImpl r (l - 1)
272241
where
273242
!_ = ACIA.checkInterval "AtCoder.Extra.Bisect.minLeftM" l r
274243

275-
-- | Takes an open interval (l, r) or (r, l).
244+
-- | Takes [l, r + 1) on `maxRight` or [r, l - 1) on `minLeft`.
276245
{-# INLINE bisectImpl #-}
277246
bisectImpl :: (HasCallStack, Monad m) => Int -> Int -> (Int -> m Bool) -> m Int
278247
bisectImpl l0 r0 p = inner l0 r0
279248
where
280249
inner l r
281-
| abs (r - l) <= 1 = pure r
250+
| abs (r - l) <= 1 = pure l
282251
| otherwise =
283252
p mid >>= \case
284253
True -> inner mid r

src/AtCoder/Extra/WaveletMatrix.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -62,7 +62,7 @@ module AtCoder.Extra.WaveletMatrix
6262
)
6363
where
6464

65-
import AtCoder.Extra.Bisect
65+
import AtCoder.Extra.Bisect (lowerBound)
6666
import AtCoder.Extra.WaveletMatrix.Raw qualified as Rwm
6767
import Control.Monad
6868
import Data.Vector.Algorithms.Intro qualified as VAI

src/AtCoder/Extra/WaveletMatrix/BitVector.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -151,7 +151,7 @@ selectKthIn0 ::
151151
selectKthIn0 bv l r k
152152
| k < 0 || nZeros <= k = Nothing
153153
-- note that `rank0` takes exclusive index
154-
| otherwise = Just . maxRight l r $ \i -> rank0 bv (i + 1) - rankL0 < k + 1
154+
| otherwise = Just . maxRight l r $ \i -> rank0 bv i - rankL0 < k + 1
155155
where
156156
nZeros = rank0 bv r - rankL0
157157
rankL0 = rank0 bv l
@@ -175,7 +175,7 @@ selectKthIn1 ::
175175
selectKthIn1 bv l r k
176176
| k < 0 || nOnes <= k = Nothing
177177
-- note that `rank1` takes exclusive index
178-
| otherwise = Just . maxRight l r $ \i -> rank1 bv (i + 1) - rankL1 < k + 1
178+
| otherwise = Just . maxRight l r $ \i -> rank1 bv i - rankL1 < k + 1
179179
where
180180
nOnes = rank1 bv r - rankL1
181181
rankL1 = rank1 bv l

test/Tests/Extra/Bisect.hs

Lines changed: 4 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -79,7 +79,10 @@ prop_maxRight = QC.testProperty "maxRight" $ do
7979
pure . QC.conjoin $
8080
map
8181
( \(!l, !r) ->
82-
naiveMaxRightIn l r (<= boundary) xs == maxRight l r (\i -> xs VG.! i <= boundary)
82+
let expected = naiveMaxRightIn l r (<= boundary) xs
83+
res = maxRight l r (\i -> xs VG.! (i - 1) <= boundary)
84+
in QC.counterexample (show ((l, r), boundary, xs)) $
85+
expected QC.=== res
8386
)
8487
lrs
8588

verify/app/yosupo-enumerate-palindromes.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -25,13 +25,13 @@ main = do
2525
-- \| . . .
2626
let i = i0 `div` 2
2727
let maxLen = min i (n - 1 - i)
28-
d <- max 0 . subtract 1 <$> maxRightM 0 (maxLen + 1) (testAt i)
28+
d <- max 0 . subtract 1 <$> maxRightM 0 (maxLen + 1) (testAt i . pred)
2929
pure $ 2 * d + 1
3030
| otherwise = do
3131
-- .|. . .
3232
let i = i0 `div` 2
3333
let maxLen = min (i + 1) (n - (i + 1))
34-
d <- max 0 . subtract 1 <$> maxRightM 0 (maxLen + 1) (testMid i)
34+
d <- max 0 . subtract 1 <$> maxRightM 0 (maxLen + 1) (testMid i . pred)
3535
pure $ 2 * d
3636
where
3737
-- \| . j.

0 commit comments

Comments
 (0)