Skip to content

Commit 40e53fc

Browse files
committed
Avoid unsafeCoerce with prime sieves
1 parent ecef15a commit 40e53fc

File tree

2 files changed

+8
-91
lines changed

2 files changed

+8
-91
lines changed

Math/NumberTheory/Primes/Counting/Impl.hs

Lines changed: 6 additions & 74 deletions
Original file line numberDiff line numberDiff line change
@@ -35,7 +35,6 @@ import Data.Bits
3535
import Data.Int
3636
import qualified Data.Vector.Unboxed as U
3737
import qualified Data.Vector.Unboxed.Mutable as MU
38-
import Unsafe.Coerce (unsafeCoerce)
3938

4039
-- | Maximal allowed argument of 'primeCount'. Currently 8e18.
4140
primeCountMaxArg :: Integer
@@ -415,87 +414,20 @@ cpGpAr = runSTUArray $ do
415414
-------------------------------------------------------------------------------
416415
-- Prime counting
417416

418-
rMASK :: Int
419-
rMASK = finiteBitSize (0 :: Word) - 1
420-
421-
wSHFT :: (Bits a, Num a) => a
422-
wSHFT = if finiteBitSize (0 :: Word) == 64 then 6 else 5
423-
424-
tOPB :: Int
425-
tOPB = finiteBitSize (0 :: Word) `shiftR` 1
426-
427-
tOPM :: (Bits a, Num a) => a
428-
tOPM = (1 `shiftL` tOPB) - 1
429-
430417
-- find the n-th set bit in a list of PrimeSieves,
431418
-- aka find the (n+3)-rd prime
432419
countToNth :: Int -> [PrimeSieve] -> Integer
433420
countToNth !_ [] = error "countToNth: Prime stream ended prematurely"
434-
countToNth !n (PS v0 bs : more) = go n 0
435-
where
436-
wa :: U.Vector Word
437-
wa = unsafeCoerce bs
438-
439-
go !k i
440-
| i >= (U.length bs + rMASK) `shiftR` wSHFT
441-
= countToNth k more
442-
| otherwise
443-
= let w = U.unsafeIndex wa i
444-
bc = popCount w
445-
in if bc < k
446-
then go (k-bc) (i+1)
447-
else let j = bc - k
448-
px = top w j bc
449-
in v0 + toPrim (px + (i `shiftL` wSHFT))
421+
countToNth !n (PS v0 bs : more) = case nthBitIndex (Bit True) n bs of
422+
Just i -> v0 + toPrim i
423+
Nothing -> countToNth (n - countBits bs) more
450424

451425
-- count all set bits in a chunk, do it wordwise for speed.
452426
countAll :: PrimeSieve -> Int
453-
countAll (PS _ bs) = go 0 0
454-
where
455-
wa :: U.Vector Word
456-
wa = unsafeCoerce bs
457-
458-
go !ct i
459-
| i >= (U.length bs + rMASK) `shiftR` wSHFT
460-
= ct
461-
| otherwise
462-
= go (ct + popCount (U.unsafeIndex wa i)) (i+1)
463-
464-
-- Find the j-th highest of bc set bits in the Word w.
465-
top :: Word -> Int -> Int -> Int
466-
top w j bc = go 0 tOPB tOPM bn w
467-
where
468-
!bn = bc-j
469-
go !_ _ !_ !_ 0 = error "Too few bits set"
470-
go bs 0 _ _ wd = if wd .&. 1 == 0 then error "Too few bits, shift 0" else bs
471-
go bs a msk ix wd =
472-
case popCount (wd .&. msk) of
473-
lc | lc < ix -> go (bs+a) a msk (ix-lc) (wd `unsafeShiftR` a)
474-
| otherwise ->
475-
let !na = a `shiftR` 1
476-
in go bs na (msk `unsafeShiftR` na) ix wd
427+
countAll (PS _ bs) = countBits bs
477428

478429
-- count set bits between two indices (inclusive)
479430
-- start and end must both be valid indices and start <= end
480431
countFromTo :: Int -> Int -> MU.MVector s Bit -> ST s Int
481-
countFromTo start end ba = do
482-
let wa = (unsafeCoerce :: MU.MVector s Bit -> MU.MVector s Word) ba
483-
let !sb = start `shiftR` wSHFT
484-
!si = start .&. rMASK
485-
!eb = end `shiftR` wSHFT
486-
!ei = end .&. rMASK
487-
count !acc i
488-
| i == eb = do
489-
w <- MU.unsafeRead wa i
490-
return (acc + popCount (w `shiftL` (rMASK - ei)))
491-
| otherwise = do
492-
w <- MU.unsafeRead wa i
493-
count (acc + popCount w) (i+1)
494-
if sb < eb
495-
then do
496-
w <- MU.unsafeRead wa sb
497-
count (popCount (w `shiftR` si)) (sb+1)
498-
else do
499-
w <- MU.unsafeRead wa sb
500-
let !w1 = w `shiftR` si
501-
return (popCount (w1 `shiftL` (rMASK - ei + si)))
432+
countFromTo start end =
433+
fmap countBits . U.unsafeFreeze . MU.slice start (end - start + 1)

Math/NumberTheory/Primes/Sieve/Eratosthenes.hs

Lines changed: 2 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -39,7 +39,6 @@ import Math.NumberTheory.Primes.Sieve.Indexing
3939
import Math.NumberTheory.Primes.Types
4040
import Math.NumberTheory.Roots
4141
import Math.NumberTheory.Utils.FromIntegral
42-
import Unsafe.Coerce (unsafeCoerce)
4342

4443
iXMASK :: Num a => a
4544
iXMASK = 0xFFFFF
@@ -77,9 +76,6 @@ lastIndex = sieveBits - 1
7776
sieveRange :: Int
7877
sieveRange = 30 * sieveBytes
7978

80-
wSHFT :: (Bits a, Num a) => a
81-
wSHFT = if finiteBitSize (0 :: Word) == 64 then 6 else 5
82-
8379
-- | Compact store of primality flags.
8480
data PrimeSieve = PS !Integer {-# UNPACK #-} !(U.Vector Bit)
8581

@@ -309,21 +305,10 @@ growCache offset plim old = do
309305
else fill j (indx+1)
310306
fill (num+1) start
311307

312-
-- Danger: relies on start and end being the first resp. last
313-
-- index in a Word
314-
-- Do not use except in growCache and psieveFrom
315308
{-# INLINE countFromToWd #-}
316309
countFromToWd :: Int -> Int -> MU.MVector s Bit -> ST s Int
317-
countFromToWd start end ba = do
318-
let wa = (unsafeCoerce :: MU.MVector s Bit -> MU.MVector s Word) ba
319-
let !sb = start `shiftR` wSHFT
320-
!eb = end `shiftR` wSHFT
321-
count !acc i
322-
| eb < i = return acc
323-
| otherwise = do
324-
w <- MU.unsafeRead wa i
325-
count (acc + popCount w) (i+1)
326-
count 0 sb
310+
countFromToWd start end =
311+
fmap countBits . U.unsafeFreeze . MU.slice start (end - start + 1)
327312

328313
-- | @'psieveFrom' n@ creates the list of 'PrimeSieve's starting roughly
329314
-- at @n@. Due to the organisation of the sieve, the list may contain

0 commit comments

Comments
 (0)