Add `isPrime` and `divides` to Euler.hs.

This commit is contained in:
Jesse D. McDonald 2015-09-02 20:06:03 -05:00
parent 39772d8b2b
commit 7d015132e9
7 changed files with 21 additions and 30 deletions

View File

@ -9,9 +9,11 @@ module Euler
, whenM
, unlessM
, primesTo
, isPrimeArray
, isPrimeArrayTo
, primes
, isPrime
, primeFactors
, divides
, zipArraysWith
, RangeIx(..)
, divisors
@ -60,26 +62,30 @@ whenM mc m = mc >>= (\c -> when c m)
unlessM mc m = mc >>= (\c -> unless c m)
primesTo n = LST.runST $ do
isPrime <- LST.strictToLazyST (newArray (2, n) 1 :: ST s (STUArray s Integer Word8))
isPrimeArr <- LST.strictToLazyST (newArray (2, n) 1 :: ST s (STUArray s Integer Word8))
let primesFrom m = if m > n then return [] else do
p <- LST.strictToLazyST (readArray isPrime m)
if p == 0 then primesFrom (m+1) else do
LST.strictToLazyST $ forM_ [2*m,3*m..n] $ \i -> writeArray isPrime i 0
(m:) <$> primesFrom (m+1)
p <- LST.strictToLazyST (readArray isPrimeArr m)
if p == 0 then primesFrom (m+1) else fmap (m:) $ do
LST.strictToLazyST $ forM_ [2*m,3*m..n] $ \i -> do
writeArray isPrimeArr i 0
primesFrom (m+1)
primesFrom 2
isPrimeArray n = runSTUArray $ do
isPrime <- newArray (2, n) 1 :: ST s (STUArray s Integer Word8)
forM_ [2..n] $ \m -> whenM ((/= 0) <$> readArray isPrime m) $ do
forM_ [2*m,3*m..n] $ \i -> writeArray isPrime i 0
return isPrime
isPrimeArrayTo n = runSTUArray $ do
isPrimeArr <- newArray (2, n) 1 :: ST s (STUArray s Integer Word8)
forM_ [2..n] $ \m -> whenM ((/= 0) <$> readArray isPrimeArr m) $ do
forM_ [2*m,3*m..n] $ \i -> writeArray isPrimeArr i 0
return isPrimeArr
primes :: [Integer]
--primes = let go (!p:xs) = p : go [ x | x <- xs, x `mod` p /= 0 ] in go [2..]
--primes = let go (!p:xs) = p : go [ x | x <- xs, not (p `divides` x) ] in go [2..]
primes = go 1000000
where
go n = primesTo n ++ dropWhile (<= n) (go (2*n))
isPrime :: Integer -> Bool
isPrime n = n >= 2 && not (any (`divides` n) $ takeWhile ((<=n).(^2)) primes)
primeFactors :: Integer -> [Integer]
primeFactors n = go n primes
where
@ -90,6 +96,9 @@ primeFactors n = go n primes
| (q, 0) <- n `divMod` p = p : go q (p:ps)
| otherwise = go n ps
divides :: Integral a => a -> a -> Bool
a `divides` b = b `mod` a == 0
class Ix a => RangeIx a where
intersectBounds :: (a, a) -> (a, a) -> (a, a)

View File

@ -8,9 +8,6 @@
import Euler
isPrime :: Integer -> Bool
isPrime n = n >= 2 && not (any (\p -> n `mod` p == 0) $ takeWhile (< n) primes)
nPrimes a b = length $ takeWhile isPrime $ map (\n -> n^2 + a*n + b) [0..]
main = print $ uncurry (*) $ snd $ maximumBy (compare `on` fst) $

View File

@ -17,7 +17,5 @@ rotations n = map (fromDigits . take (length digits))
main = do
let limit = 1000000 - 1
let isPrimeArr = isPrimeArray limit
let isPrime n = (isPrimeArr!n) /= 0
let circular n = all isPrime $ rotations n
print $ length $ filter circular [2..limit]

View File

@ -5,8 +5,4 @@ import Euler
import Data.Array.Unboxed
truncations n = map fromDigits $ filter (not . null) $ inits (toDigits n) ++ tails (toDigits n)
isPrimeArr = isPrimeArray 1000000
isPrime n = n >= 2 && isPrimeArr!n /= 0
main = print $ sum $ take 11 $ filter (all isPrime . truncations) [11..]

View File

@ -9,7 +9,4 @@ import Euler
pandigitals = map fromDigits $ go 9
where go 0 = []; go n = reverse (sort (permutations [1..n])) ++ go (n-1)
isPrime n = not $ any (\p -> n `mod` p == 0) $
takeWhile (<= floor (sqrt (fromIntegral n))) primes
main = print $ head $ filter isPrime pandigitals

View File

@ -14,10 +14,6 @@
import Euler
import Debug.Trace
isPrime :: Integer -> Bool
isPrime n = n >= 2 && all (\p -> n `mod` p /= 0) smallPrimes
where smallPrimes = takeWhile (<= floor (sqrt (fromIntegral n))) primes
main = print $ head $ do
base <- primes
let digits = toDigits base

View File

@ -18,8 +18,6 @@ module Main where
import Euler
isPrime n = n >= 2 && not (any (\p -> n `mod` p == 0) $ takeWhile ((<= n) . (^2)) primes)
-- diagonals of an m by m spiral; m = 2*n + 1.
allDiags = 1 : zipWith (+) allDiags (concat $ map (replicate 4) [2,4..])
allDiags' = map isPrime allDiags