{-# LANGUAGE BangPatterns #-}
module Math.NumberTheory.Primes.Factorisation.TrialDivision
( trialDivisionWith
, trialDivisionTo
, trialDivisionPrimeWith
, trialDivisionPrimeTo
) where
import Math.NumberTheory.Primes.Sieve.Eratosthenes
import Math.NumberTheory.Powers.Squares
import Math.NumberTheory.Primes.Types
import Math.NumberTheory.Utils
trialDivisionWith :: [Integer] -> Integer -> [(Integer, Word)]
trialDivisionWith prs n
| n < 0 = trialDivisionWith prs (-n)
| n == 0 = error "trialDivision of 0"
| n == 1 = []
| otherwise = go n (integerSquareRoot' n) prs
where
go !m !r (p:ps)
| r < p = [(m,1)]
| otherwise =
case splitOff p m of
(0,_) -> go m r ps
(k,q) -> (p,k) : if q == 1
then []
else go q (integerSquareRoot' q) ps
go m _ _ = [(m,1)]
trialDivisionTo :: Integer -> Integer -> [(Integer, Word)]
trialDivisionTo bd
| bd < 100 = trialDivisionTo 100
| bd < 10000000 = trialDivisionWith (map unPrime $ primeList $ primeSieve bd)
| otherwise = trialDivisionWith (takeWhile (<= bd) $ map unPrime $ (psieveList >>= primeList))
trialDivisionPrimeWith :: [Integer] -> Integer -> Bool
trialDivisionPrimeWith prs n
| n < 0 = trialDivisionPrimeWith prs (-n)
| n < 2 = False
| otherwise = go n (integerSquareRoot' n) prs
where
go !m !r (p:ps) = r < p || m `rem` p /= 0 && go m r ps
go _ _ _ = True
trialDivisionPrimeTo :: Integer -> Integer -> Bool
trialDivisionPrimeTo bd
| bd < 100 = trialDivisionPrimeTo 100
| bd < 10000000 = trialDivisionPrimeWith (map unPrime $ primeList $ primeSieve bd)
| otherwise = trialDivisionPrimeWith (takeWhile (<= bd) $ map unPrime $ (psieveList >>= primeList))