Sieve Of Eratosthenes Algorithms
Implemented in any programming language
The sieve of Eratosthenes is a simple algorithm created by an ancient Greek mathematician, for finding all prime numbers up to a specified integer. The algorithm is often used to compare the syntax of programming languages and the speed of compilers, or interpreters.
The algorithm:
Build a list of all the integers greater than one and less than or equal to n. Strike out the multiples of all primes less than or equal to the square root of n, then the numbers that are left are the primes.
The algorithms below all compute prime numbers, but not all of them really implement excatly the Eratosthenes' algorithm.
Ada Awk Basic Bash C C++ C# D Caml Eiffel Euphoria F# Forth Fortran Go Haskell Java JavaScript Julia Lisp Lua Nim Oberon OCaml Oz Pascal Perl PHP Prolog Python Rebol Rexx Ruby Rust Scala Scheme Scriptol Smalltalk Swift Tcl
Ada
procedure Eratosthenes(Result : out Integer) is
size : constant := 8190;
k, prime : Natural;
count : Integer;
type Ftype is array (0 .. Size) of Boolean;
Flags : Ftype;
begin
for Iter in 1 .. 10 loop
count := 0;
for i in 0 .. size loop
Flags (i) := True;
end loop;
for i in 0 .. size loop
if Flags (i) then
prime := i + i + 3;
k := i + prime;
while k <= size loop
Flags (k) := False;
k := k + prime;
end loop;
count := count + 1;
end if;
end loop;
end loop;
Result := count;
end Eratosthenes;
Awk
BEGIN {
top = 50;
n = (ARGV[1] < 1) ? 1 : ARGV[1];
while (n--)
{
for(i=2; i <= top; flags[i++]=1);
for (i=2; i <= top; i++)
{
if (flags[i])
{
for (k = i + i; k <= top; k += i)
{
flags[k] = 0;
}
}
}
}
exit;
}
Basic
QuickBasic, reference manual for Apple Macintosh, by Microsoft.
defint a-z
size=50
dim flags(50)
for i=2 to size
flags(i)=-1
next
for i=2 to sqr(size)
if flags(i) then
for k=i*i to size step i
flags(k)=0
next
end if
next
for i=0 to size
if flags(i) then print i;
next
print
Older Basic:
1010 REM Quite BASIC Math Project 2000 CLS 2030 LET L = 50 2050 ARRAY N 2070 FOR I = 1 TO L 2080 LET N[I] = I 2090 NEXT I 2110 LET P = 2 2120 PRINT P 2140 FOR I = P TO L STEP P 2150 LET N[I] = 0 2160 NEXT I 2180 LET P = P + 1 2190 IF P = L THEN END 2200 IF N[P] <> 0 THEN GOTO 2120 ELSE GOTO 2180
Bash
#!/bin/bash
# Sieve of Eratosthenes from the bash scripting guide
UPPER_LIMIT=$1
let SPLIT=UPPER_LIMIT/2
Primes=( '' $(seq $UPPER_LIMIT) )
i=1
until (( ( i += 1 ) > SPLIT ))
do
if [[ -n $Primes[i] ]]
then
t=$i
until (( ( t += i ) > UPPER_LIMIT ))
do
Primes[t]=
done
fi
done
echo ${Primes[*]}
exit 0
C
/* Sieve Of Erathosthenes by Denis Sureau */ #include <stdlib.h>#include <stdio.h> void eratosthenes(int top) { int all[10000]; int idx = 0; int prime = 3; int x, j; printf("1 "); while(prime <= top) { for(x = 0; x < top; x++) { if(all[x] == prime) goto skip; } printf("%d ", prime); j = prime; while(j <= (top / prime)) { all[idx++] = prime * j; j += 1; } skip: prime+=2; } puts(""); return; } int main(int argc, char **argv) { if(argc == 2) eratosthenes(atoi(argv[1])); else eratosthenes(50); return 0; }
Another version with no goto submitted by an user:
#include <stdio.h>
#include <stdlib.h>
/* Sieve by Baavgai */
void sieve(int size) {
int i,j;
char *sieve = (char *) calloc(size, 1);
for (i=2; i*i <= size; i++) {
if (!sieve[i]) {
for(j = i+i; j < size; j+=i) { sieve[j] = 1; }
}
}
for (i=2; i<size; i++) {
if (!sieve[i]) { printf("%d ", i); }
}
printf("\n");
free(sieve);
}
int main() {
sieve(100);
return 0;
}
C++
/* Sieve Of Erathosthenes by Denis Sureau */ #include <stdlib.h>#include <stdio.h> #include <iostream> #include <vector> void eratosthenes(int top) { std::vector <int> all = { top }; int idx = 0; std::cout << "1 "; for(int prime = 3; prime <= top; prime += 2) { bool flag = false; for(int x = 0; x < top; x++) { if(all[x] == prime) { flag = true; break; } } if(flag == false) { std::cout << prime << " "; int j = prime; while(j <= (top / prime)) { all[idx++] = prime * j; j += 1; } } } std::cout << std::endl; return; } int main(int argc, char **argv) { if(argc == 2) eratosthenes(atoi(argv[1])); else eratosthenes(50); return 0; }
C# (C Sharp)
using System;
class App
{
public static int Main(String[] args)
{
int num;
bool[] flags = new bool[51];
long i, k;
int count = 0;
num = System.Convert.ToInt32(args[0]);
if(num < 1) num = 1;
while(num-- > 0)
{
count = 0;
for(i = 2; i <= 50; i++)
{
flags[i] = true;
}
for(i = 2; i <= 50; i++)
{
if(flags[i])
{
for(k = i + i; k <= 50; k += i)
{
flags[k] = false;
}
count++;
}
}
}
Console.WriteLine("Count: " + count.ToString());
return(0);
}
}
D
import std.stdio;
bool[8191] flags;
int main()
{
int i, count, prime, k, iter;
writeln("10 iterations");
for (iter = 1; iter <= 10; iter++)
{
count = 0;
flags[] = 1;
for (i = 0; i < flags.length; i++)
{
if (flags[i])
{
prime = i + i + 3;
k = i + prime;
while (k < flags.length)
{
flags[k] = 0;
k += prime;
}
count += 1;
}
}
}
writefln("%d primes", count);
return 0;
}
Source: Documentation du langage D.
Eiffel
class FIBONACCI
feature
fib (k: INTEGER): INTEGER is
require
pre_fib: k >= 0 do
if k = 0 then
Result := 0
else
if k = 1 then
Result := 1
else
Result := fib (k-2) + fib (k-1) end
end;
Euphoria
-- Sieve Of Erathosthenes by Derek Parnell
-- Language: Euphoria v3.1.1 (www.rapideuphoria.com)
include get.e
procedure eratosthenes(integer target)
sequence sieve
integer next_prime
integer limit
sieve = repeat(0, target)
limit = floor(power(target, 0.5))
sieve[1] = 1
next_prime = 2
while next_prime <= target and next_prime != 0 do
if next_prime <= limit then
for i = next_prime + next_prime to target by next_prime do
sieve[i] = 1
end for
end if
printf(1, "%d ", next_prime)
next_prime = find_from(0, sieve, next_prime+1)
end while
return
end procedure
procedure main(sequence argv)
integer n
n = 50
if length(argv) >= 3 then
argv = value(argv[3])
n = argv[2]
end if
eratosthenes(n)
end procedure
main( command_line() )
Source code
F# (F Sharp)
let is_prime n =
let max = int_of_float (Math.Sqrt( float_of_int n ))
not ({ 2 .. max } |> Seq.filter ( fun d -> n%d = 0) |> Seq.nonempty)
let primes = [0 .. top] |> List.filter is_prime
Forth
7919 2/ constant maxp
: primes ( -- n )
here maxp 1 FILL
1 ( count, including 2 )
maxp 0 DO
I here + C@ IF
I 2* 3 + ( dup .) DUP I + ( prime current )
begin DUP maxp U<
while 0 over here + C!
over +
repeat
2drop 1+
then
loop ;
primes . \ 1000
Fortran
* Sieve of Eratosthenes by Chuck Bouldin
top = 50
logical*2 flags(top)
integer*2 i,j,k,count,iter,prime
n = long(362)
do 92 iter = 1,10
count=0
i=0
do 10 i = 1,top
10 flags(i) = .true.
do 91 i = 1,top
if (.not. flags(i)) go to 91
prime = i + i + 3
count = count + 1
k = i + prime
if (k .gt. top) go to 91
do 60 j = k, top, prime
60 flags(j) = .false.
91 continue
92 continue
write (9,*) count," primes in ",(long(362)-n)/60.0," seconds "
pause
end
Go
(Selon la documentation du language)
func Generate(ch chan<- int) {
for i := 2; ; i++ {
ch <- i
}
}
func Filter(in <-chan int, out chan<- int, prime int) {
for {
i := <-in // Receive value from 'in'.
if i%prime != 0 {
out <- i
}
}
}
func main() {
ch := make(chan in
go Generate(ch)
for i := 0; i < 10; i++ {
prime := <-ch
fmt.Println(prime)
ch1 := make(chan int)
go Filter(ch, ch1, prime)
ch = ch1
}
}
Haskell
primes = sieve [ 2.. ] where sieve (p:x) = p : sieve [ n | n <- x, n `mod` p > 0 ]
Java
public class Eratosthenes
{
public static void main(String[] args)
{
int N = Integer.parseInt(args[0]);
boolean[] isPrime = new boolean[N + 1];
for (int i = 2; i <= N; i++)
isPrime[i] = true;
for (int i = 2; i*i <= N; i++)
{
if (isPrime[i])
{
for (int j = i; i*j <= N; j++)
isPrime[i*j] = false;
}
}
int primes = 0;
for (int i = 2; i <= N; i++)
{
if (isPrime[i])
System.out.println(" " + i);
}
}
}
JavaScript
<script language="JavaScript">
/* Sieve Of Erathosthenes by Denis Sureau */
function Eratosthenes(element, top)
{
var all = new Uint8Array(new ArrayBuffer(top));
var idx = 0;
var prime = 3;
var x, j;
element.innerHTML = "1 ";
while(prime <= top)
{
var flag = true;
for(x = 0; x < top; x++)
{
if(all[x] == prime)
{
flag = false;
break;
}
}
if(flag)
{
element.innerHTML += prime + " ";
j = prime;
while(j <= (top / prime))
{
all[idx++] = prime * j;
j += 1;
}
}
prime += 2;
}
element.innerHTML += "<br>";
return;
}
</script>
<div id="primediv" onclick="Eratosthenes(this, 50);">
Click to start...
</div>
Julia
# Sieve of Erasthotenes in Julia
# By Denis Sureau 14/2/2014
function eratosthenes(size)
all=ones(Int32, size)
println(1)
println(2)
idx = 1
prime = 3
while prime <= size
if !in(prime, all)
println(prime)
idx += 1
j = prime
while (j <= (size / prime))
all = [all, prime * j]
j += 1
end
end
prime += 2
end
println
end
eratosthenes(50)
Source
Lisp
(define divides (m n) (= (mod n m) 0))
(define seq (m n)
(if (> m n) `()
(cons m (seq (+ 1 m) n))))
(define remove-multiples (n L)
(if (null? L) `()
(if (divides (n (car l))
(remove-multiples n (cdr L))
(cons (car L)
(remove-multiples n (cdr L))))))
Lua
-- By Darren Kirby
x = arg[1]
y = math.floor(math.sqrt(x))
primes = {}
set = {}
for i=2,x do
table.insert(set, i)
end
function isFactor(index, value)
if math.mod(value, checkint) == 0 then
table.remove(set, index)
end
end
while set[1] <= y do
table.insert(primes, set[1])
checkint = set[1]
table.remove(set, 1)
for i,v in ipairs(set) do isFactor(i,v) end
end
for key, value in primes do
io.write(value .. " ")
end
for key, value in set do
io.write(value .. " ")
end
print()
Nim
import math
proc eratosthenes(n): auto =
prime = newSeq[int8](n+1)
prime[0] = 1;
prime[1] = 1
for i in 0 .. int sqrt(float n):
if prime[i] == 0:
for j in countup(i*i, n, i):
prime[j] = 1
discard eratosthenes(1000)
Source: Hookrace/Converted from one of many Python solution.
Oberon
MODULE Eratosthenes;
(* Active Oberon Demo *)
IMPORT Streams;
CONST
N = 50;
Terminate = -1;
VAR log: Streams.Stream;
TYPE
Sieve = POINTER TO SieveDesc;
SieveDesc = RECORD (OBJECT)
VAR prime, n: INTEGER; available: BOOLEAN; next: Sieve;
PROCEDURE Set (i: INTEGER);
BEGIN {EXCLUSIVE}
PASSIVATE (~available); n := i; available := TRUE
END Set;
PROCEDURE Change;
BEGIN {EXCLUSIVE} available := FALSE
END Change;
PROCEDURE & Init;
BEGIN prime := 0; available := FALSE; next := NIL
END Init;
BEGIN {PARALLEL(2)}
LOOP
PASSIVATE (available);
IF n = Terminate THEN
IF next # NIL THEN next.Set (n) END;
EXIT
ELSE
IF prime = 0 THEN
log.Int(n); log.Ln;
prime := n; NEW (next)
ELSIF (n MOD prime) # 0 THEN next.Set (n)
END;
Change
END
END
END SieveDesc;
Gen = POINTER TO GenDesc;
GenDesc = RECORD
VAR s: Sieve; i: INTEGER;
BEGIN {PARALLEL(2)}
NEW (s);
FOR i := 2 TO N-1 DO s.Set (i) END;
s.Set (Terminate)
END GenDesc;
PROCEDURE Start*;
VAR g: Gen;
BEGIN
NEW(log, "Eratosthenes", 70);
NEW (g)
END Start;
END Eratosthenes.
Eratosthenes.Start
Ocaml
(* (c) 2003 David Van Horn - Licensed under the Academic Free License version 2.0 *)
open List
type integer = Int of int
let number_two = Int(2)
let number_zero = Int(0)
let is_less_than_two (Int n) = n < 2
let incr (Int n) = Int(n + 1)
let decr (Int n) = Int(n - 1)
let is_number_zero (Int n) = n = 0
let iota n =
let rec loop curr counter =
if is_less_than_two counter then []
else curr::(loop (incr curr) (decr counter))
in
loop number_two n
let sieve lst =
let rec choose_pivot = function
| [] -> []
| car::cdr when is_number_zero car ->
car::(choose_pivot cdr)
| car::cdr ->
car::(choose_pivot (do_sieve car (decr car) cdr))
and do_sieve step current lst =
match lst with
| [] -> []
| car::cdr ->
if is_number_zero current
then number_zero::(do_sieve step (decr step) cdr)
else car::(do_sieve step (decr current) cdr)
in
choose_pivot lst
let is_prime n =
match rev (sieve (iota n)) with
x::_ -> not (is_number_zero x)
Oz
functor
import System Application
define Args N Flags Start Stop in
[Args] = {Application.getArgs plain}
N = {String.toInt Args}
Start = 2
Top = 50
Flags = {BitArray.new Start Stop}
for I in Start..Top do {BitArray.set Flags I} end
for I in 1..N do
for J in Start..Top do
if {BitArray.test Flags J} then
for K in J+J..Top;J do {BitArray.clear Flags K} end
end
end
end
{System.showInfo "Count: "#{BitArray.card Flags}}
{Application.exit 0}
end
Pascal
program Eratosthenes;
const N=1000;
var a:ARRAY[1..N] of boolean;
i,j,m:word;
begin
for i:=1 TO N do a[i]:=TRUE;
m:=trunc(sqrt(N));
for i:=2 to m do
if a[i] then for j:=2 to N DIV i do a[i*j]:=FALSE;
for i:=1 to N do if a[i] then write(i:4);
end.
Perl
Contributed by users:
#!/usr/bin/perl
use strict;
use integer;
my $count = 0;
my $top = 50;
my @flags = (0 .. $top);
for my $i (2 .. int(sqrt($top)) + 1)
{
next unless defined $flags[$i];
for (my $k=$i+$i; $k <= $top; $k+=$i)
{
undef $flags[$k];
}
}
print "Here is the list of primes from 1 to $top:\n";
for my $j ( 1 .. $top)
{
print ("$j ") && $count++ if defined
$flags[$j];
}
print "\n";
print "Number of primes found: $count\n";
Source code
PHP
<?php
/* Sieve Of Erathosthenes by Denis Sureau */
function eratosthenes($n)
{
$all=array();
$prime=1;
echo 1," ",2;
$i=3;
while($i<=$n)
{
if(!in_array($i,$all))
{
echo " ",$i;
$prime+=1;
$j=$i;
while($j<=($n/$i))
{
array_push($all,$i*$j);
$j+=1;
}
}
$i+=2;
}
echo "\n";
return;
}
eratosthenes(50);
?>
Prolog
% Sieve of Eratosthene % Le Huitouze and Ridoux translated by DGS $ erathostenes :- freeze(L,prime(L)), list_of_ints(2,L). $ prime([X|L]) :- write(X), nl, freeze(L,sieve(X,L,Canal)), freeze(Canal,prime(Canal)). $ sieve(X,[Nb|L],Canal) :- mod(Nb,X,0), !, freeze(L,sieve(X,L,Canal)). $ sieve(X,[Nb|L],[Nb|Canal2]) :- freeze(L,sieve(X,L,Canal2)). $ list_of_ints(X,[X|L]) :- plus(X,1,X1), list_of_ints(X1,L)..
Python 3
def eratosthenes(n):
all = []
prime = 1
print("1, 2,")
i = 3
while (i <= n):
if i not in all:
print(i, ",")
prime += 1
j = i
while (j <= (n / i)):
all.append(i * j)
j += 1
i += 2
print("\n")
eratosthenes(100)
Contribution by a user, more conformant to the Sieve of Erastosthenes algorithm:
# Sieve by Baavgai def eratosthenes(n):
sieve = [ True for i in range(n+1) ]
def markOff(pv):
for i in range(pv+pv, n+1, pv):
sieve[i] = False
markOff(2)
for i in range(3, n+1):
if sieve[i]:
markOff(i)
return [ i for i in range(1, n+1) if sieve[i] ]
print(eratosthenes(100))
Rebol
ctr: to-integer to-string system/script/args
ctr: either ctr < 1 [ 1 ] [ ctr ]
top: 50
while [ ctr > 0 ]
[
flags: copy []
for i 0 top 1
[
insert tail flags 1
]
flags: head flags
for i 2 top 1
[
p: pick flags i
if p = 1
[
k: i + i
while [ k <= top ]
[
change at flags k 0
k: k + i
]
]
]
ctr: ctr - 1
]
Rexx
limit = 50
isPrime. = 1
do n=2 to limit
if isPrime.n then
call anotherPrime n
end
exit 0
anotherPrime
arg prime
say right( prime, length( limit ) )
do multiple=prime by prime to limit
isPrime.multiple = 0
end
return
Ruby
# sieve of Eratosthenes from the ruby distro
top = Integer(ARGV.shift || 100)
sieve = []
for i in 2 .. top
sieve[i] = i
end
for i in 2 .. Math.sqrt(top)
next unless sieve[i]
(i*i).step(top, i) do |j|
sieve[j] = nil
end
end
puts sieve.compact.join " "
Rust
fn sieve(bound: uint) -> ~[uint] {
let mut primes = std::vec::from_fn(bound+1, |num| num == 2 || num & 1 != 0);
for num in count(3u, 2).filter(|&num| primes[num]).take_while(|&num| num * num <= bound) {
for j in range_step_inclusive(num*num, bound, num) {
primes[j] = false;
}
}
primes.move_iter().enumerate().skip(2).filter_map(|(i, p)| if p {Some(i)} else {None}).collect::<~[uint]>()
}
fn main() {
assert_eq!(sieve(20), ~[2, 3, 5, 7, 11, 13, 17, 19]);
}
Source: jsanders on Github.
Scala
object Sieve
{
def ints(n: Int): Stream[Int] =
Stream.cons(n, ints(n+1))
def primes(nums: Stream[Int]): Stream[Int] =
Stream.cons(nums.head, primes ((nums tail) filter (x => x % nums.head != 0)) )
def main(args: Array[String]): Unit =
{
val n = Integer.parseInt(args(0))
System.out.println(primes(ints(2)) take n toList)
}
}
Scheme
(define (sieve-of-eratosthenes n)
(let ((table (make-bit-string (- n 2) #t)))
(define (prime? k) (bit-string-ref table (- k 2)))
(define (not-prime! k) (bit-string-clear! table (- k 2)))
(loop ((for k (in-range (from 2) (up-to n))))
(if (prime? k)
(loop ((for i (in-range (from (* 2 k)) (up-to n) (by k))))
(not-prime! i))))
(collect-list (for k (in-range (from 2) (up-to n)))
(if (prime? k))
k)))
Scriptol
# Sieve of Eratosthènes by Denis Sureau
array sieve(int top)
array all = [ top ]
array somelist = [1]
int idx = 0
for int prime in 3 -- top step 2
if prime in all ? continue
somelist.push(prime)
int j = prime
while j <= (top / prime)
all[idx] = prime * j
idx + 1
j + 1
/while
/for
return somelist
array a = sieve(1000)
print a
Smalltalk
" Sieve of Erastosthenes in Smalltalk by Rob Hoelz
Object subclass: #Sieve
instanceVariableNames: 'primes'
classVariableNames: ''
poolDictionaries: ''
category: nil.
!Sieve class methodsFor: 'instance creation'!
new: limit
|r|
r := super new.
r init: limit.
^r
! !
!Sieve methodsFor: 'instance initialization'!
init: limit
primes := Array new: limit.
primes at: 1 put: 0.
2 to: limit do: [:x| primes at: x put: 1]
! !
!Sieve methodsFor: 'prime generation'!
generate
|currPrime|
currPrime := 2.
[((currPrime * currPrime) <= (primes size))]
whileTrue: [self removeMultiples: currPrime. currPrime := self nextPrime: currPrime]
! !
!Sieve methodsFor: 'printing'!
printPrimes
|index|
index := 1.
primes do: [:x| (x = 1) ifTrue:
[Transcript show:(index displayString).Transcript show: ' ']. index := index + 1].
Transcript cr
! !
!Sieve methodsFor: 'private'!
removeMultiples: currPrime
|index|
index := currPrime * 2.
[(index <= (primes size))] whileTrue: [primes at: index put: 0. index := index + currPrime]
!
nextPrime: currPrime
|index|
index := currPrime + 1.
[(index <= (primes size))] whileTrue: [(1 = (primes at: index)) ifTrue: [^index]. index := index + 1].
^(primes size)
! !
|argv limit s|
argv := Smalltalk arguments.
limit := (argv at: 1) asInteger.
s := Sieve new: limit.
s generate.
s printPrimes.
Swift
func eratosthenes(n: Int) -> sieveResult{ var sieve = [Int] 0..< n var i = 1 let top = Int(sqrt(Double(n))) return sieveResult { while ++i < n { if sieve[i] != 0 { if i <= top { for notPrime in stride(from: i*i, to: n, by: i) { sieve[notPrime] = 0 } } return i } } return nil } }
Tcl
# By Sam Shen
set n 50
narray create sieve $n
sieve status
sieve map {
if ![]
{
inc = @0 + 2;
for (i = @0 + inc; i < @#0; i += inc)
{
[i] = 1;
}
}
}
sieve map
{
if ![]
{
printf("%4d ", @0 + 2);
}
post { printf("\n"); }
}
See also:
Programs on this page are public domain, or written by myself or contributed by users.

