{-# LANGUAGE CPP #-}
{-# LANGUAGE LambdaCase #-}
module Math.NumberTheory.ArithmeticFunctions.Mertens
( mertens
) where
import qualified Data.Vector.Unboxed as U
import Math.NumberTheory.Powers.Cubes
import Math.NumberTheory.Powers.Squares
import Math.NumberTheory.ArithmeticFunctions.Moebius
mertens :: Word -> Int
mertens 0 = 0
mertens 1 = 1
mertens x = sumMultMoebius lookupMus (\n -> sfunc (x `quot` n)) [1 .. x `quot` u]
where
u = (integerSquareRoot x + 1) `max` ((integerCubeRoot x) ^ (2 :: Word) `quot` 2)
sfunc :: Word -> Int
sfunc y
= 1
- sum [ U.unsafeIndex mes (fromIntegral $ y `quot` n) | n <- [y `quot` u + 1 .. kappa] ]
+ fromIntegral kappa * U.unsafeIndex mes (fromIntegral nu)
- sumMultMoebius lookupMus (\n -> fromIntegral $ y `quot` n) [1 .. nu]
where
nu = integerSquareRoot y
kappa = y `quot` (nu + 1)
cacheSize :: Word
cacheSize = u `max` (x `quot` u) `max` integerSquareRoot x
mus :: U.Vector Moebius
mus = sieveBlockMoebius 1 cacheSize
lookupMus :: Word -> Moebius
lookupMus i = U.unsafeIndex mus (fromIntegral (i - 1))
mes :: U.Vector Int
mes = U.scanl' go 0 mus
where
go acc = \case
MoebiusN -> acc - 1
MoebiusZ -> acc
MoebiusP -> acc + 1
sumMultMoebius :: (Word -> Moebius) -> (Word -> Int) -> [Word] -> Int
sumMultMoebius mu f = foldl go 0
where
go acc i = case mu i of
MoebiusN -> acc - f i
MoebiusZ -> acc
MoebiusP -> acc + f i