Skip to content

Instantly share code, notes, and snippets.

@WillNess
Last active March 17, 2018 16:24
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save WillNess/a0a9647c873fd560e00b2e52b3a8256a to your computer and use it in GitHub Desktop.
Save WillNess/a0a9647c873fd560e00b2e52b3a8256a to your computer and use it in GitHub Desktop.

-- https://stackoverflow.com/questions/49312746/how-to-properly-define-an-haskell-function-isprime

f n = map (mod n) [1..(round . sqrt . fromInteger) n]
primes = map fst $ filter (all (/=0).tail.snd) $ map (id &&& f) [2..]

f n = map (mod n) [2..(round . sqrt . fromInteger) n]
primes = filter (all (/=0).f) [2..]

g n = and [mod n i > 0 | i <- [2..(round . sqrt . fromInteger) n]]
primes = [ n | n <- [2..], g n]

primes = [ n | n <- [2..] , and [mod n i > 0 | i <- takeWhile ((<=n).(^2)) [2..]]]

primes = 2 : [ n | n <- [3..] , and [mod n i > 0 | i <- takeWhile ((<=n).(^2)) primes]]

primes = ps
 where
 ps = 2 : [n | (r:q:_, px) <- (zip . tails . (2:) . map (^2)) ps (inits ps),
               n <- [r+1..q-1],  all ((> 0) . rem n) px]

primes = 2 : ps
 where
 ps = 3 : [n | (r:q:_, px) <- (zip . tails . (3:) . map (^2)) ps (inits ps),
               n <- [r+2,r+4..q-2],  all ((> 0) . rem n) px]

ps = 2 : [n | (r:q:_, px) <- (zip . tails . (2:) . map (^2) <*> inits) ps,
              (n,True)    <- assocs ( accumArray (const id) True (r+1,q-1)
                                [(m,False) | p <- px, s <- [ (r+p)`div`p*p ], 
                                             m <- [s,s+p..q-1]] :: UArray Int Bool )]

For positive x, modulo x == mod x. Then,

mapMod = (\x -> map (mod x)) 
       = (\x -> (map . mod) x) 
       =        (map . mod)

and it is so short and clear that many would prefer just to use it right away, whether as a lambda expression or the last one, without the argument, which is known as a pointfree code ("without points" i.e. explicit arguments).

Having to remember a whole separate function name for something this short and trivial can be distracting. Thus we get

f n = map (mod n) [1..(round . sqrt . fromInteger) n]
    = [mod n i | i <- [1..(round . sqrt . fromInteger) n]]
    = 0 : [mod n i | i <- [2..(round . sqrt . fromInteger) n]]
    = 0 : g n

g n = [mod n i | i <- [2..(round . sqrt . fromInteger) n]]

primes = filter (\n -> all (> 0) (tail $ f n)) [2..]
       = [n | n <- [2..], all (> 0) (tail $ f n)]
       = [n | n <- [2..], all (> 0) (tail $ 0 : g n)]
       = [n | n <- [2..], all (> 0) (g n)]
       = [n | n <- [2..], all (> 0)
                           [mod n i | i <- [2..(round . sqrt . fromInteger) n]]]
       = [n | n <- [2..], all (> 0)
                           [mod n i | i <- takeWhile (\i-> i^2 <= n) [2..]]]
       = 2 : [n | n <- [3..], all (> 0)
                               [mod n i | i <- takeWhile (\i-> i^2 <= n) [2..]]]
       = 2 : [n | n <- [3..], all (> 0)
                               [mod n i | i <- takeWhile (\i-> i^2 <= n) primes]]
       = 2 : [n | n <- [3..], isPrime n]

Thus we've derived the definitions

primes :: [Int]
primes = 2 : filter isPrime [3..]
isPrime n = all (> 0) [mod n i | i <- takeWhile (\i-> i^2 <= n) primes]
          = and [mod n i > 0 | i <- takeWhile (\i-> i^2 <= n) primes]
          = foldr (\i r -> i*i > n || (mod n i > 0 && r)) True primes

Trying it out,

~> filter isPrime [150..200]
[151,157,163,167,173,179,181,191,193,197,199]

~> :sprint primes                                 -- 13*13 = 169
primes = 2 : 3 : 5 : 7 : 11 : 13 : 17 : _         -- 17*17 = 289
primes = 2 : (`filter` [3..]) (isPrime primes) 
       = fix $ (2 :) . (`filter` [3..]) . isPrime
isPrime primes n = foldr (\i r -> i*i > n || (mod n i > 0 && r)) True primes
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment