One-dimensional cellular automata: Difference between revisions

From Rosetta Code
Content added Content deleted
No edit summary
m (Fixed lang tags.)
Line 15: Line 15:


=={{header|Ada}}==
=={{header|Ada}}==
<lang ada>
<lang ada>with Ada.Text_IO; use Ada.Text_IO;
with Ada.Text_IO; use Ada.Text_IO;


procedure Cellular_Automata is
procedure Cellular_Automata is
Line 57: Line 56:
Step (Culture);
Step (Culture);
end loop;
end loop;
end Cellular_Automata;
end Cellular_Automata;</lang>
</lang>
The implementation defines Petri dish type with Boolean items identifying whether a place is occupied by a living cell. State transition is determined by a simple Boolean expression of three arguments. Sample output:
The implementation defines Petri dish type with Boolean items identifying whether a place is occupied by a living cell. State transition is determined by a simple Boolean expression of three arguments. Sample output:
<pre>
<pre>
Line 74: Line 72:
=={{header|ALGOL 68}}==
=={{header|ALGOL 68}}==
===Using the low level packed arrays of BITS manipulation operators===
===Using the low level packed arrays of BITS manipulation operators===
<lang algol68>INT stop generation = 9;
<pre>
INT stop generation = 9;
INT universe width = 20;
INT universe width = 20;
FORMAT alive or dead = $b("#","_")$;
FORMAT alive or dead = $b("#","_")$;
Line 117: Line 114:
FI;
FI;
universe := next universe
universe := next universe
OD
OD</lang>
</pre>
===Using high level BOOL arrays===
===Using high level BOOL arrays===
<lang algol68>INT stop generation = 9;
<pre>
INT stop generation = 9;
INT upb universe = 20;
INT upb universe = 20;
FORMAT alive or dead = $b("#","_")$;
FORMAT alive or dead = $b("#","_")$;
Line 155: Line 150:
next universe[UPB universe] := couple(universe[UPB universe - 1: ]);
next universe[UPB universe] := couple(universe[UPB universe - 1: ]);
universe := next universe
universe := next universe
OD
OD</lang>
</pre>
Output:
Output:
<lang algol68>Generation 0: _###_##_#_#_#_#__#__
<pre>
Generation 0: _###_##_#_#_#_#__#__
Generation 1: _#_#####_#_#_#______
Generation 1: _#_#####_#_#_#______
Generation 2: __##___##_#_#_______
Generation 2: __##___##_#_#_______
Line 168: Line 161:
Generation 7: __##_____#__________
Generation 7: __##_____#__________
Generation 8: __##________________
Generation 8: __##________________
Generation 9: __##________________
Generation 9: __##________________</lang>
</pre>
=={{header|AutoHotkey}}==
=={{header|AutoHotkey}}==
ahk [http://www.autohotkey.com/forum/viewtopic.php?t=44657&postdays=0&postorder=asc&start=147 discussion]
ahk [http://www.autohotkey.com/forum/viewtopic.php?t=44657&postdays=0&postorder=asc&start=147 discussion]
Line 382: Line 374:
}
}
return 0;
return 0;
}</lang>
}
</lang>


The output is:
The output is:
Line 501: Line 492:


=={{header|Forth}}==
=={{header|Forth}}==
: init ( bits count -- )
<lang forth>: init ( bits count -- )
0 do dup 1 and c, 2/ loop drop ;
0 do dup 1 and c, 2/ loop drop ;
20 constant size
create state $2556e size init 0 c,
: .state
cr size 0 do
state i + c@ if ." #" else space then
loop ;
: ctable create does> + c@ ;
ctable rules $68 8 init
: gen
state c@ ( window )
size 0 do
2* state i + 1+ c@ or 7 and
dup rules state i + c!
loop drop ;
: life1d ( n -- )
.state 1 do gen .state loop ;


20 constant size
10 life1d
create state $2556e size init 0 c,

: .state
cr size 0 do
state i + c@ if ." #" else space then
loop ;

: ctable create does> + c@ ;
ctable rules $68 8 init

: gen
state c@ ( window )
size 0 do
2* state i + 1+ c@ or 7 and
dup rules state i + c!
loop drop ;

: life1d ( n -- )
.state 1 do gen .state loop ;

10 life1d</lang>


=={{header|Fortran}}==
=={{header|Fortran}}==
{{works with|Fortran|90 and later}}
{{works with|Fortran|90 and later}}
<lang fortran> PROGRAM LIFE_1D
<lang fortran>PROGRAM LIFE_1D
IMPLICIT NONE
LOGICAL :: cells(20) = (/ .FALSE., .TRUE., .TRUE., .TRUE., .FALSE., .TRUE., .TRUE., .FALSE., .TRUE., .FALSE., &
.TRUE., .FALSE., .TRUE., .FALSE., .TRUE., .FALSE., .FALSE., .TRUE., .FALSE., .FALSE. /)
INTEGER :: i
IMPLICIT NONE
DO i = 0, 9

WRITE(*, "(A,I0,A)", ADVANCE = "NO") "Generation ", i, ": "
LOGICAL :: cells(20) = (/ .FALSE., .TRUE., .TRUE., .TRUE., .FALSE., .TRUE., .TRUE., .FALSE., .TRUE., .FALSE., &
CALL Drawgen(cells)
.TRUE., .FALSE., .TRUE., .FALSE., .TRUE., .FALSE., .FALSE., .TRUE., .FALSE., .FALSE. /)
CALL Nextgen(cells)
END DO
INTEGER :: i
DO i = 0, 9
CONTAINS
WRITE(*, "(A,I0,A)", ADVANCE = "NO") "Generation ", i, ": "
SUBROUTINE Nextgen(cells)
CALL Drawgen(cells)
LOGICAL, INTENT (IN OUT) :: cells(:)
CALL Nextgen(cells)
END DO
LOGICAL :: left, centre, right

INTEGER :: i
CONTAINS

left = .FALSE.
DO i = 1, SIZE(cells)-1
SUBROUTINE Nextgen(cells)
centre = cells(i)
LOGICAL, INTENT (IN OUT) :: cells(:)
right = cells(i+1)
LOGICAL :: left, centre, right
INTEGER :: i
IF (left .AND. right) THEN
cells(i) = .NOT. cells(i)
ELSE IF (.NOT. left .AND. .NOT. right) THEN
cells(i) = .FALSE.
END IF
left = centre
END DO
cells(SIZE(cells)) = left .AND. right
END SUBROUTINE Nextgen
SUBROUTINE Drawgen(cells)
LOGICAL, INTENT (IN OUT) :: cells(:)
INTEGER :: i
DO i = 1, SIZE(cells)
IF (cells(i)) THEN
WRITE(*, "(A)", ADVANCE = "NO") "#"
ELSE
WRITE(*, "(A)", ADVANCE = "NO") "_"
END IF
END DO
WRITE(*,*)
END SUBROUTINE Drawgen
left = .FALSE.
END PROGRAM LIFE_1D</lang>
DO i = 1, SIZE(cells)-1
centre = cells(i)
right = cells(i+1)
IF (left .AND. right) THEN
cells(i) = .NOT. cells(i)
ELSE IF (.NOT. left .AND. .NOT. right) THEN
cells(i) = .FALSE.
END IF
left = centre
END DO
cells(SIZE(cells)) = left .AND. right
END SUBROUTINE Nextgen

SUBROUTINE Drawgen(cells)
LOGICAL, INTENT (IN OUT) :: cells(:)
INTEGER :: i
DO i = 1, SIZE(cells)
IF (cells(i)) THEN
WRITE(*, "(A)", ADVANCE = "NO") "#"
ELSE
WRITE(*, "(A)", ADVANCE = "NO") "_"
END IF
END DO
WRITE(*,*)
END SUBROUTINE Drawgen
END PROGRAM LIFE_1D</lang>
Output
Output
Generation 0: _###_##_#_#_#_#__#__
Generation 0: _###_##_#_#_#_#__#__
Line 592: Line 583:


=={{header|Haskell}}==
=={{header|Haskell}}==
<lang haskell>module Life1D where
<pre>
module Life1D where


import Data.List
import Data.List
Line 616: Line 606:
g <- newStdGen
g <- newStdGen
let oersoep = map ("_#"!!). take 36 $ randomRs(0,1) g
let oersoep = map ("_#"!!). take 36 $ randomRs(0,1) g
mapM_ print . lahmahgaan $ oersoep
mapM_ print . lahmahgaan $ oersoep</lang>
</pre>
Some output:
Some output:
<lang haskell>*Life1D> mapM_ print . lahmahgaan $ "_###_##_#_#_#_#__#__"
<pre>
*Life1D> mapM_ print . lahmahgaan $ "_###_##_#_#_#_#__#__"
"_###_##_#_#_#_#__#__"
"_###_##_#_#_#_#__#__"
"_#_#####_#_#_#______"
"_#_#####_#_#_#______"
Line 638: Line 626:
"________________________________#_#_"
"________________________________#_#_"
"_________________________________#__"
"_________________________________#__"
"____________________________________"
"____________________________________"</lang>
</pre>
=={{header|J}}==
=={{header|J}}==
life1d=: '_#'{~ (3(2=+/\) 0,],0:)^:a:
<lang j>life1d=: '_#'{~ (3(2=+/\) 0,],0:)^:a:</lang>
Example use:
Example use:
life1d ? 20 # 2
<lang j> life1d ? 20 # 2
_###_##_#_#_#_#__#__
_###_##_#_#_#_#__#__
_#_#####_#_#_#______
_#_#####_#_#_#______
__##___##_#_#_______
__##___##_#_#_______
__##___###_#________
__##___###_#________
__##___#_##_________
__##___#_##_________
__##____###_________
__##____###_________
__##____#_#_________
__##____#_#_________
__##_____#__________
__##_____#__________
__##________________
__##________________</lang>


=={{header|Java}}==
=={{header|Java}}==
Line 712: Line 699:
=={{header|Logo}}==
=={{header|Logo}}==
{{works with|UCBLogo}}
{{works with|UCBLogo}}
<lang logo>make "cell_list [0 1 1 1 0 1 1 0 1 0 1 0 1 0 1 0 0 1 0 0]
<lang logo>
make "cell_list [0 1 1 1 0 1 1 0 1 0 1 0 1 0 1 0 0 1 0 0]
make "generations 9
make "generations 9


Line 750: Line 736:
end
end


CA_1D :cell_list :generations
CA_1D :cell_list :generations</lang>
</lang>
Sample Output:
Sample Output:
<pre>
<pre>
Line 767: Line 752:


=={{header|M4}}==
=={{header|M4}}==
<lang M4>
<lang M4>divert(-1)
divert(-1)
define(`set',`define(`$1[$2]',`$3')')
define(`set',`define(`$1[$2]',`$3')')
define(`get',`defn(`$1[$2]')')
define(`get',`defn(`$1[$2]')')
Line 803: Line 787:
for(`j',1,10,
for(`j',1,10,
`show(x)`'evolve(`x',`y')`'swap(`x',x,`y')
`show(x)`'evolve(`x',`y')`'swap(`x',x,`y')
')`'show(x)
')`'show(x)</lang>
</lang>


Output:
Output:
Line 823: Line 806:
=={{header|Mathematica}}==
=={{header|Mathematica}}==
Built-in function:
Built-in function:
<lang Mathematica>CellularAutomaton[{{0,0,_}->0,{0,1,0}->0,{0,1,1}->1,{1,0,0}->0,{1,0,1}->1,{1,1,0}->1,{1,1,1}->0},{{1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1},0},12]
<lang Mathematica>
Print @@@ (% /. {1 -> "#", 0 -> "."});</lang>
CellularAutomaton[{{0,0,_}->0,{0,1,0}->0,{0,1,1}->1,{1,0,0}->0,{1,0,1}->1,{1,1,0}->1,{1,1,1}->0},{{1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1},0},12]
Print @@@ (% /. {1 -> "#", 0 -> "."});
</lang>
gives back:
gives back:
<lang Mathematica>
<lang Mathematica>###.##.#.#.#.#..#
###.##.#.#.#.#..#
#.#####.#.#.#....
#.#####.#.#.#....
.##...##.#.#.....
.##...##.#.#.....
Line 841: Line 821:
.##..............
.##..............
.##..............
.##..............
.##..............
.##..............</lang>
</lang>


=={{header|Modula-3}}==
=={{header|Modula-3}}==
Line 907: Line 886:
=={{header|Nial}}==
=={{header|Nial}}==
(life.nial)
(life.nial)
% we need a way to write a values and pass the same back
<lang nial>% we need a way to write a values and pass the same back
wi is rest link [write, pass]
wi is rest link [write, pass]
% calculate the neighbors by rotating the array left and right and joining them
% calculate the neighbors by rotating the array left and right and joining them
neighbors is pack [pass, sum [-1 rotate, 1 rotate]]
neighbors is pack [pass, sum [-1 rotate, 1 rotate]]
% calculate the individual birth and death of a single array element
% calculate the individual birth and death of a single array element
igen is fork [ = [ + [first, second], 3 first], 0 first, = [ + [first, second], 2 first], 1 first, 0 first ]
igen is fork [ = [ + [first, second], 3 first], 0 first, = [ + [first, second], 2 first], 1 first, 0 first ]
% apply that to the array
% apply that to the array
nextgen is each igen neighbors
nextgen is each igen neighbors
% 42
% 42
life is fork [ > [sum pass, 0 first], life nextgen wi, pass ]
life is fork [ > [sum pass, 0 first], life nextgen wi, pass ]</lang>
Using it
Using it
|loaddefs 'life.nial'
<lang nial>|loaddefs 'life.nial'
|I := [0,1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1,0,0]
|I := [0,1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1,0,0]
|life I
|life I</lang>


=={{header|OCaml}}==
=={{header|OCaml}}==
Line 952: Line 931:
else print_char '#'
else print_char '#'
done;
done;
print_newline()
print_newline()</lang>
</lang>


put the code above in a file named "life.ml", and then use it in the ocaml toplevel like this:
put the code above in a file named "life.ml", and then use it in the ocaml toplevel like this:
Line 1,011: Line 989:
universe.replace('0', printdead).replace('1', printlive) )
universe.replace('0', printdead).replace('1', printlive) )
universe = offendvalue + universe + offendvalue
universe = offendvalue + universe + offendvalue
universe = ''.join(neighbours2newstate[universe[i:i+3]] for i in range(cellcount))
universe = ''.join(neighbours2newstate[universe[i:i+3]] for i in range(cellcount))</lang>
</lang>
Sample output:
Sample output:
<pre>Generation 0: _###_##_#_#_#_#__#__
<pre>Generation 0: _###_##_#_#_#_#__#__
Line 1,043: Line 1,020:
=={{header|R}}==
=={{header|R}}==


<lang R>set.seed(15797, kind="Mersenne-Twister")
<lang R>
set.seed(15797, kind="Mersenne-Twister")


maxgenerations = 10
maxgenerations = 10
Line 1,076: Line 1,052:
universe <- cellularAutomata(universe, stayingAlive)
universe <- cellularAutomata(universe, stayingAlive)
cat(format(i, width=3), deadOrAlive2string(universe), "\n")
cat(format(i, width=3), deadOrAlive2string(universe), "\n")
}</lang>
}
</lang>


Sample output,
Sample output,
Line 1,201: Line 1,176:


This implementation writes the calculated patterns into an edit buffer, where the results can viewed and saved into a file if required. The edit buffer also acts as storage during calculations.
This implementation writes the calculated patterns into an edit buffer, where the results can viewed and saved into a file if required. The edit buffer also acts as storage during calculations.
<lang vedit>IT("Gen 0: ..###.##.#.#.#.#..#.....") // initial pattern
<pre>
IT("Gen 0: ..###.##.#.#.#.#..#.....") // initial pattern
#9 = Cur_Col
#9 = Cur_Col


Line 1,219: Line 1,193:
IT("Gen ") Num_Ins(#8, LEFT+NOCR) IT(": ")
IT("Gen ") Num_Ins(#8, LEFT+NOCR) IT(": ")
Reg_Ins(20)
Reg_Ins(20)
}</lang>
}
</pre>


Sample output:
Sample output:
<lang vedit>Gen 0: ..###.##.#.#.#.#..#.....
<pre>
Gen 0: ..###.##.#.#.#.#..#.....
Gen 1: ..#.#####.#.#.#.........
Gen 1: ..#.#####.#.#.#.........
Gen 2: ...##...##.#.#..........
Gen 2: ...##...##.#.#..........
Line 1,233: Line 1,205:
Gen 7: ...##.....#.............
Gen 7: ...##.....#.............
Gen 8: ...##...................
Gen 8: ...##...................
Gen 9: ...##...................
Gen 9: ...##...................</lang>
</pre>

Revision as of 14:14, 21 November 2009

Task
One-dimensional cellular automata
You are encouraged to solve this task according to the task description, using any language you may know.

Assume an array of cells with an initial distribution of live and dead cells, and imaginary cells off the end of the array having fixed values.

Cells in the next generation of the array are calculated based on the value of the cell and its left and right nearest neighbours in the current generation. If, in the following table, a live cell is represented by 1 and a dead cell by 0 then to generate the value of the cell at a particular index in the array of cellular values you use the following table:

000 -> 0  # 
001 -> 0  #
010 -> 0  # Dies without enough neighbours
011 -> 1  # Needs one neighbour to survive
100 -> 0  #
101 -> 1  # Two neighbours giving birth
110 -> 1  # Needs one neighbour to survive
111 -> 0  # Starved to death.

Ada

<lang ada>with Ada.Text_IO; use Ada.Text_IO;

procedure Cellular_Automata is

  type Petri_Dish is array (Positive range <>) of Boolean;
  procedure Step (Culture : in out Petri_Dish) is
     Left  : Boolean := False;
     This  : Boolean;
     Right : Boolean;
  begin
     for Index in Culture'First..Culture'Last - 1 loop
        Right := Culture (Index + 1);
        This  := Culture (Index);
        Culture (Index) := (This and (Left xor Right)) or (not This and Left and Right);
        Left := This;
     end loop;
     Culture (Culture'Last) := Culture (Culture'Last) and not Left;
  end Step;
  
  procedure Put (Culture : Petri_Dish) is
  begin
     for Index in Culture'Range loop
        if Culture (Index) then
           Put ('#');
        else
           Put ('_');
        end if;
     end loop;
  end Put;
  Culture : Petri_Dish :=
     (  False, True, True,  True, False, True,  True, False, True, False, True,
        False, True, False, True, False, False, True, False, False
     );

begin

  for Generation in 0..9 loop
     Put ("Generation" & Integer'Image (Generation) & ' ');
     Put (Culture);
     New_Line;
     Step (Culture);
  end loop;

end Cellular_Automata;</lang> The implementation defines Petri dish type with Boolean items identifying whether a place is occupied by a living cell. State transition is determined by a simple Boolean expression of three arguments. Sample output:

Generation 0 _###_##_#_#_#_#__#__
Generation 1 _#_#####_#_#_#______
Generation 2 __##___##_#_#_______
Generation 3 __##___###_#________
Generation 4 __##___#_##_________
Generation 5 __##____###_________
Generation 6 __##____#_#_________
Generation 7 __##_____#__________
Generation 8 __##________________
Generation 9 __##________________

ALGOL 68

Using the low level packed arrays of BITS manipulation operators

<lang algol68>INT stop generation = 9; INT universe width = 20; FORMAT alive or dead = $b("#","_")$;

BITS universe := 2r01110110101010100100;

  # universe := BIN ( ENTIER ( random * max int ) ); #

INT upb universe = bits width; INT lwb universe = bits width - universe width + 1;

PROC couple = (BITS parent, INT lwb, upb)BOOL: (

 SHORT INT sum := 0;
 FOR bit FROM lwb TO upb DO
   sum +:= ABS (bit ELEM parent)
 OD;
 sum = 2

);

FOR generation FROM 0 WHILE

 printf(($"Generation "d": "$, generation,
        $f(alive or dead)$, []BOOL(universe)[lwb universe:upb universe],
        $l$));
  1. WHILE # generation < stop generation DO
 BITS next universe := 2r0;  
 
 # process the first event horizon manually #
 IF couple(universe,lwb universe,lwb universe + 1) THEN 
   next universe := 2r10
 FI;
 
 # process the middle kingdom in a loop #
 FOR bit FROM lwb universe + 1 TO upb universe - 1 DO 
   IF couple(universe,bit-1,bit+1) THEN
     next universe := next universe OR 2r1
   FI;
   next universe := next universe SHL 1
 OD; 
 # process the last event horizon manually #
 IF couple(universe, upb universe - 1, upb universe) THEN 
   next universe := next universe OR 2r1
 FI;
 universe := next universe

OD</lang>

Using high level BOOL arrays

<lang algol68>INT stop generation = 9; INT upb universe = 20; FORMAT alive or dead = $b("#","_")$;

BITS bits universe := 2r01110110101010100100;

  # bits universe := BIN ( ENTIER ( random * max int ) ); #

[upb universe] BOOL universe := []BOOL(bits universe)[bits width - upb universe + 1:];

PROC couple = (REF[]BOOL parent)BOOL: (

 SHORT INT sum := 0;
 FOR bit FROM LWB parent TO UPB parent DO
   sum +:= ABS (parent[bit])
 OD;
 sum = 2

);

FOR generation FROM 0 WHILE

 printf(($"Generation "d": "$, generation,
        $f(alive or dead)$, universe,
        $l$));
  1. WHILE # generation < stop generation DO
 [UPB universe]BOOL next universe;
 
 # process the first event horizon manually #
 next universe[1] := couple(universe[:2]);
 
 # process the middle kingdom in a loop #
 FOR bit FROM LWB universe + 1 TO UPB universe - 1 DO 
   next universe[bit] := couple(universe[bit-1:bit+1])
 OD; 
 # process the last event horizon manually #
 next universe[UPB universe] := couple(universe[UPB universe - 1: ]);
 universe := next universe

OD</lang> Output: <lang algol68>Generation 0: _###_##_#_#_#_#__#__ Generation 1: _#_#####_#_#_#______ Generation 2: __##___##_#_#_______ Generation 3: __##___###_#________ Generation 4: __##___#_##_________ Generation 5: __##____###_________ Generation 6: __##____#_#_________ Generation 7: __##_____#__________ Generation 8: __##________________ Generation 9: __##________________</lang>

AutoHotkey

ahk discussion <lang autohotkey>n := 22, n1 := n+1, v0 := v%n1% := 0  ; set grid dimensions, and fixed cells

Loop % n {  ; draw a line of checkboxes

  v%A_Index% := 0
  Gui Add, CheckBox, % "y10 w17 h17 gCheck x" A_Index*17-5 " vv" A_Index

} Gui Add, Button, x+5 y6, step  ; button to step to next generation Gui Show Return

Check:

  GuiControlGet %A_GuiControl%             ; set cells by the mouse

Return

ButtonStep:  ; move to next generation

  Loop % n
     i := A_Index-1, j := i+2, w%A_Index% := v%i%+v%A_Index%+v%j% = 2
  Loop % n
     GuiControl,,v%A_Index%, % v%A_Index% := w%A_Index%

Return

GuiClose:  ; exit when GUI is closed ExitApp</lang>

BASIC

Works with: QuickBasic version 4.5
Translation of: Java

<lang qbasic>DECLARE FUNCTION life$ (lastGen$) DECLARE FUNCTION getNeighbors! (group$) CLS start$ = "_###_##_#_#_#_#__#__" numGens = 10 FOR i = 0 TO numGens - 1 PRINT "Generation"; i; ": "; start$ start$ = life$(start$) NEXT i

FUNCTION getNeighbors (group$) ans = 0 IF (MID$(group$, 1, 1) = "#") THEN ans = ans + 1 IF (MID$(group$, 3, 1) = "#") THEN ans = ans + 1 getNeighbors = ans END FUNCTION

FUNCTION life$ (lastGen$) newGen$ = "" FOR i = 1 TO LEN(lastGen$) neighbors = 0 IF (i = 1) THEN 'left edge IF MID$(lastGen$, 2, 1) = "#" THEN neighbors = 1 ELSE neighbors = 0 END IF ELSEIF (i = LEN(lastGen$)) THEN 'right edge IF MID$(lastGen$, LEN(lastGen$) - 1, 1) = "#" THEN neighbors = 1 ELSE neighbors = 0 END IF ELSE 'middle neighbors = getNeighbors(MID$(lastGen$, i - 1, 3)) END IF

IF (neighbors = 0) THEN 'dies or stays dead with no neighbors newGen$ = newGen$ + "_" END IF IF (neighbors = 1) THEN 'stays with one neighbor newGen$ = newGen$ + MID$(lastGen$, i, 1) END IF IF (neighbors = 2) THEN 'flips with two neighbors IF MID$(lastGen$, i, 1) = "#" THEN newGen$ = newGen$ + "_" ELSE newGen$ = newGen$ + "#" END IF END IF NEXT i life$ = newGen$ END FUNCTION</lang> Output:

Generation 0 : _###_##_#_#_#_#__#__
Generation 1 : _#_#####_#_#_#______
Generation 2 : __##___##_#_#_______
Generation 3 : __##___###_#________
Generation 4 : __##___#_##_________
Generation 5 : __##____###_________
Generation 6 : __##____#_#_________
Generation 7 : __##_____#__________
Generation 8 : __##________________
Generation 9 : __##________________

C

<lang c>#include <stdio.h>

  1. include <stdlib.h>
  2. include <string.h>
  1. define SPACEDIM 20
  2. define GENERATION 10
  1. define ALIVE '#'
  2. define DEAD '_'

/* what happens out of the space: is the world a circle, or

  it really ends? */
  1. define CCOND 0

char space[SPACEDIM]; char tspace[SPACEDIM];

int rrand(int l) {

  return (int)((double)l*(double)rand()/((double)RAND_MAX+1.0));

}

void initspace(char *s, int d) {

  int i;
  static const char *tp = "_###_##_#_#_#_#__#__";
  for(i=0; (i < strlen(tp)) && (i<d) ; i++)
  {
     s[i] = (tp[i] == ALIVE) ? 1 : 0;
  }

}

void initspace_random(char *s, int d) {

  int i;
  for (i=0; i<d; i++)
  {
     s[i] = rrand(2);
  }

}

/*

  count the Number of Alive in the Neighbourhood
  two kind of "bound condition" can be choosen
  at compile time
  • /

int nalive(const char *s, int i, int d) {

  switch ( CCOND )
  {
     case 0:
        return ((i-1)<0 ? 0 : s[i-1]) + ((i+1)<d ? s[i+1] : 0 );
     case 1:
        return s[ (i+1)%d ] + s[ (i+d-1)%d ];
  }

}

void evolve(const char *from, char *to, int d) {

  int i;
  
  for(i=0; i<d; i++)
  {
     if ( from[i] )
     {  /* 0 neighbour is solitude, 2 are one too much; 1, he's a friend */
        if ( nalive(from, i, d) == 1 )
        {
           to[i] = 1;
        } else {
           to[i] = 0;
        }
     } else {
        if ( nalive(from, i, d) == 2 )
        { /* there must be two, to make a child ... */
           to[i] = 1;
        } else {
           to[i] = 0;
        }
     }
  }

}

void show(const char *s, int d) {

 int i;
 
 for(i=0; i<d; i++)
 {
   printf("%c", s[i] ? ALIVE : DEAD);
 }
 printf("\n");

}


int main() {

  int i;
  char *from, *to, *t;
  
  initspace(space, SPACEDIM);
  from = space; to = tspace;
  for(i=0; i<GENERATION; i++)
  {
         show(from, SPACEDIM);
         evolve(from, to, SPACEDIM);
         t = from; from = to; to = t;
  }
  printf("\n");
  initspace_random(space, SPACEDIM);
  from = space; to = tspace;
  for(i=0; i<GENERATION; i++)
  {
         show(from, SPACEDIM);
         evolve(from, to, SPACEDIM);
         t = from; from = to; to = t;
  }
  return 0;

}</lang>

The output is:

_###_##_#_#_#_#__#__
_#_#####_#_#_#______
__##___##_#_#_______
__##___###_#________
__##___#_##_________
__##____###_________
__##____#_#_________
__##_____#__________
__##________________
__##________________

#_###__#_#_#_#####_#
_##_#___#_#_##___##_
_###_____#_###___##_
_#_#______##_#___##_
__#_______###____##_
__________#_#____##_
___________#_____##_
_________________##_
_________________##_
_________________##_

Common Lisp

Based upon the Ruby version. <lang lisp>(defun value (x)

 (assert (> (length x) 1))
 (coerce x 'simple-bit-vector))

(defun count-neighbors-and-self (value i)

 (flet ((ref (i)
          (if (array-in-bounds-p value i)
              (bit value i)
              0)))
   (declare (inline ref))
   (+ (ref (1- i))
      (ref i)
      (ref (1+ i)))))

(defun next-cycle (value)

 (let ((new-value (make-array (length value) :element-type 'bit)))
   (loop for i below (length value)
         do (setf (bit new-value i)
                  (if (= 2 (count-neighbors-and-self value i))
                      1
                      0)))
   new-value))

(defun print-world (value &optional (stream *standard-output*))

 (loop for i below (length value)
       do (princ (if (zerop (bit value i)) #\. #\#)
                 stream))
 (terpri stream))</lang>

<lang lisp>CL-USER> (loop for previous-value = nil then value

              for value = #*01110110101010100100 then (next-cycle value)
              until (equalp value previous-value)
              do (print-world value))

.###.##.#.#.#.#..#.. .#.#####.#.#.#...... ..##...##.#.#....... ..##...###.#........ ..##...#.##......... ..##....###......... ..##....#.#......... ..##.....#.......... ..##................</lang>

E

<lang e>def step(state, rule) {

   var result := state(0, 1) # fixed left cell
   for i in 1..(state.size() - 2) {
       # Rule function receives the substring which is the neighborhood
       result += E.toString(rule(state(i-1, i+2)))
   }
   result += state(state.size() - 1) # fixed right cell
   return result

}

def play(var state, rule, count, out) {

   out.print(`0 | $state$\n`)
   for i in 1..count {
       state := step(state, rosettaRule)
       out.print(`$i | $state$\n`)
   }
   return state

}</lang>

<lang e>def rosettaRule := [

   "   " => " ",
   "  #" => " ",
   " # " => " ",
   " ##" => "#",
   "#  " => " ",
   "# #" => "#",
   "## " => "#",
   "###" => " ",

].get

? play(" ### ## # # # # # ", rosettaRule, 9, stdout) 0 | ### ## # # # # # 1 | # ##### # # # 2 | ## ## # # 3 | ## ### # 4 | ## # ## 5 | ## ### 6 | ## # # 7 | ## # 8 | ## 9 | ##

  1. value: " ## "</lang>

Forth

<lang forth>: init ( bits count -- )

 0 do dup 1 and c, 2/ loop drop ;

20 constant size create state $2556e size init 0 c,

.state
 cr size 0 do
   state i + c@ if ." #" else space then
 loop ;
ctable create does> + c@ ;

ctable rules $68 8 init

gen
 state c@ ( window )
 size 0 do
   2*  state i + 1+ c@ or  7 and
   dup rules state i + c!
 loop drop ;
life1d ( n -- )
 .state 1 do gen .state loop ;

10 life1d</lang>

Fortran

Works with: Fortran version 90 and later

<lang fortran>PROGRAM LIFE_1D

 IMPLICIT NONE
 LOGICAL :: cells(20) = (/ .FALSE., .TRUE., .TRUE., .TRUE., .FALSE., .TRUE., .TRUE., .FALSE., .TRUE., .FALSE., &
                           .TRUE., .FALSE., .TRUE., .FALSE., .TRUE., .FALSE., .FALSE., .TRUE., .FALSE., .FALSE. /)
 INTEGER :: i
 
 DO i = 0, 9
    WRITE(*, "(A,I0,A)", ADVANCE = "NO") "Generation ", i, ": "
    CALL Drawgen(cells)
    CALL Nextgen(cells)
 END DO

CONTAINS

 SUBROUTINE Nextgen(cells)
   LOGICAL, INTENT (IN OUT) :: cells(:)
   LOGICAL :: left, centre, right
   INTEGER :: i
  
   left = .FALSE.
   DO i = 1, SIZE(cells)-1
      centre = cells(i)
      right = cells(i+1)
      IF (left .AND. right) THEN
         cells(i) = .NOT. cells(i)
      ELSE IF (.NOT. left .AND. .NOT. right) THEN
         cells(i) = .FALSE.
      END IF
      left = centre
   END DO
   cells(SIZE(cells)) = left .AND. right
 END SUBROUTINE Nextgen
 SUBROUTINE Drawgen(cells)
   LOGICAL, INTENT (IN OUT) :: cells(:)
   INTEGER :: i
  
   DO i = 1, SIZE(cells)
      IF (cells(i)) THEN
         WRITE(*, "(A)", ADVANCE = "NO") "#"
      ELSE
         WRITE(*, "(A)", ADVANCE = "NO") "_"
      END IF
   END DO
   WRITE(*,*)
 END SUBROUTINE Drawgen
 

END PROGRAM LIFE_1D</lang> Output

Generation 0: _###_##_#_#_#_#__#__ 
Generation 1: _#_#####_#_#_#______ 
Generation 2: __##___##_#_#_______ 
Generation 3: __##___###_#________ 
Generation 4: __##___#_##_________ 
Generation 5: __##____###_________ 
Generation 6: __##____#_#_________ 
Generation 7: __##_____#__________ 
Generation 8: __##________________ 
Generation 9: __##________________

Haskell

<lang haskell>module Life1D where

import Data.List import System.Random import Control.Monad import Control.Arrow

bnd :: [Char] -> Char bnd bs =

  case bs of
       "_##" -> '#'
       "#_#" -> '#'
       "##_" -> '#'
       _     -> '_'

donxt xs = unfoldr(\xs -> case xs of [_,_] -> Nothing ;

                                     _ -> Just (bnd $ take 3 xs, drop 1 xs))  $ '_':xs++"_"

lahmahgaan xs = init.until (liftM2 (==) last (last. init)) (ap (++)(return. donxt. last)) $ [xs, donxt xs]

main = do

  g <- newStdGen
  let oersoep = map ("_#"!!). take 36 $ randomRs(0,1) g 
  mapM_ print . lahmahgaan $ oersoep</lang>

Some output: <lang haskell>*Life1D> mapM_ print . lahmahgaan $ "_###_##_#_#_#_#__#__" "_###_##_#_#_#_#__#__" "_#_#####_#_#_#______" "__##___##_#_#_______" "__##___###_#________" "__##___#_##_________" "__##____###_________" "__##____#_#_________" "__##_____#__________" "__##________________"

  • Life1D> main

"__##_##__#____###__#__#_______#_#_##" "__#####_______#_#______________#_###" "__#___#________#________________##_#" "________________________________###_" "________________________________#_#_" "_________________________________#__" "____________________________________"</lang>

J

<lang j>life1d=: '_#'{~ (3(2=+/\) 0,],0:)^:a:</lang> Example use: <lang j> life1d ? 20 # 2 _###_##_#_#_#_#__#__ _#_#####_#_#_#______ __##___##_#_#_______ __##___###_#________ __##___#_##_________ __##____###_________ __##____#_#_________ __##_____#__________ __##________________</lang>

Java

This example requires a starting generation of at least length two (which is what you need for anything interesting anyway). <lang java>public class Life{ public static void main(String[] args) throws Exception{ String start= "_###_##_#_#_#_#__#__"; int numGens = 10; for(int i= 0; i < numGens; i++){ System.out.println("Generation " + i + ": " + start); start= life(start); } }

public static String life(String lastGen){ String newGen= ""; for(int i= 0; i < lastGen.length(); i++){ int neighbors= 0; if (i == 0){//left edge neighbors= lastGen.charAt(1) == '#' ? 1 : 0; } else if (i == lastGen.length() - 1){//right edge neighbors= lastGen.charAt(i - 1) == '#' ? 1 : 0; } else{//middle neighbors= getNeighbors(lastGen.substring(i - 1, i + 2)); }

if (neighbors == 0){//dies or stays dead with no neighbors newGen+= "_"; } if (neighbors == 1){//stays with one neighbor newGen+= lastGen.charAt(i); } if (neighbors == 2){//flips with two neighbors newGen+= lastGen.charAt(i) == '#' ? "_" : "#"; } } return newGen; }

public static int getNeighbors(String group){ int ans= 0; if (group.charAt(0) == '#') ans++; if (group.charAt(2) == '#') ans++; return ans; } }</lang> Output:

Generation 0: _###_##_#_#_#_#__#__
Generation 1: _#_#####_#_#_#______
Generation 2: __##___##_#_#_______
Generation 3: __##___###_#________
Generation 4: __##___#_##_________
Generation 5: __##____###_________
Generation 6: __##____#_#_________
Generation 7: __##_____#__________
Generation 8: __##________________
Generation 9: __##________________

Works with: UCBLogo

<lang logo>make "cell_list [0 1 1 1 0 1 1 0 1 0 1 0 1 0 1 0 0 1 0 0] make "generations 9

to evolve :n ifelse :n=1 [make "nminus1 item :cell_count :cell_list][make "nminus1 item :n-1 :cell_list] ifelse :n=:cell_count[make "nplus1 item 1 :cell_list][make "nplus1 item :n+1 :cell_list] ifelse ((item :n :cell_list)=0) [ ifelse (and (:nminus1=1) (:nplus1=1)) [output 1][output (item :n :cell_list)] ][ ifelse (and (:nminus1=1) (:nplus1=1)) [output 0][ ifelse and (:nminus1=0) (:nplus1=0) [output 0][output (item :n :cell_list)]] ] end

to CA_1D :cell_list :generations make "cell_count count :cell_list (print ") make "printout " repeat :cell_count [ make "printout word :printout ifelse (item repcount :cell_list)=1 ["#]["_] ] (print "Generation "0: :printout)

repeat :generations [

      (make "cell_list_temp [])
      repeat :cell_count[
            (make "cell_list_temp (lput (evolve repcount) :cell_list_temp))
      ]
      make "cell_list :cell_list_temp
      make "printout "
      repeat :cell_count [
      	      make "printout word :printout ifelse (item repcount :cell_list)=1 ["#]["_]
      ]
      (print "Generation  word repcount ": :printout)

] end

CA_1D :cell_list :generations</lang> Sample Output:

Generation 0: _###_##_#_#_#_#__#__
Generation 1: _#_#####_#_#_#______
Generation 2: __##___##_#_#_______
Generation 3: __##___###_#________
Generation 4: __##___#_##_________
Generation 5: __##____###_________
Generation 6: __##____#_#_________
Generation 7: __##_____#__________
Generation 8: __##________________
Generation 9: __##________________

M4

<lang M4>divert(-1) define(`set',`define(`$1[$2]',`$3')') define(`get',`defn(`$1[$2]')') define(`setrange',`ifelse(`$3',`',$2,`define($1[$2],$3)`'setrange($1,

  incr($2),shift(shift(shift($@))))')')

dnl throw in sentinels at each end (0 and size+1) to make counting easy define(`new',`set($1,size,eval($#-1))`'setrange($1,1,

  shift($@))`'set($1,0,0)`'set($1,$#,0)')

define(`for',

  `ifelse($#,0,``$0,
  `ifelse(eval($2<=$3),1,
  `pushdef(`$1',$2)$4`'popdef(`$1')$0(`$1',incr($2),$3,`$4')')')')

define(`show',

  `for(`k',1,get($1,size),`get($1,k) ')')

dnl swap(`a',a,`b') using arg stack for temp define(`swap',`define(`$1',$3)`'define(`$3',$2)') define(`nalive',

  `eval(get($1,decr($2))+get($1,incr($2)))')

setrange(`live',0,0,1,0) setrange(`dead',0,0,0,1) define(`nv',

  `ifelse(get($1,z),0,`get(dead,$3)',`get(live,$3)')')

define(`evolve',

  `for(`z',1,get($1,size),
     `set($2,z,nv($1,z,nalive($1,z)))')')

new(`a',0,1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1,0,0) set(`b',size,get(`a',size))`'set(`b',0,0)`'set(`b',incr(get(`a',size)),0) define(`x',`a') define(`y',`b') divert for(`j',1,10,

  `show(x)`'evolve(`x',`y')`'swap(`x',x,`y')

')`'show(x)</lang>

Output:

0 1 1 1 0 1 1 0 1 0 1 0 1 0 1 0 0 1 0 0
0 1 0 1 1 1 1 1 0 1 0 1 0 1 0 0 0 0 0 0
0 0 1 1 0 0 0 1 1 0 1 0 1 0 0 0 0 0 0 0
0 0 1 1 0 0 0 1 1 1 0 1 0 0 0 0 0 0 0 0
0 0 1 1 0 0 0 1 0 1 1 0 0 0 0 0 0 0 0 0
0 0 1 1 0 0 0 0 1 1 1 0 0 0 0 0 0 0 0 0
0 0 1 1 0 0 0 0 1 0 1 0 0 0 0 0 0 0 0 0
0 0 1 1 0 0 0 0 0 1 0 0 0 0 0 0 0 0 0 0
0 0 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
0 0 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0
0 0 1 1 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0 0

Mathematica

Built-in function: <lang Mathematica>CellularAutomaton[{{0,0,_}->0,{0,1,0}->0,{0,1,1}->1,{1,0,0}->0,{1,0,1}->1,{1,1,0}->1,{1,1,1}->0},{{1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1},0},12] Print @@@ (% /. {1 -> "#", 0 -> "."});</lang> gives back: <lang Mathematica>###.##.#.#.#.#..#

  1. .#####.#.#.#....

.##...##.#.#..... .##...###.#...... .##...#.##....... .##....###....... .##....#.#....... .##.....#........ .##.............. .##.............. .##.............. .##.............. .##..............</lang>

Modula-3

Translation of: Ada

Modula-3 provides a module Word for doing bitwise operations, but it segfaults when trying to use BOOLEAN types, so we use INTEGER instead. <lang modula3>MODULE Cell EXPORTS Main;

IMPORT IO, Fmt, Word;

VAR culture := ARRAY [0..19] OF INTEGER {0, 1, 1, 1,

                                        0, 1, 1, 0, 
                                        1, 0, 1, 0, 
                                        1, 0, 1, 0, 
                                        0, 1, 0, 0};

PROCEDURE Step(VAR culture: ARRAY OF INTEGER) =

 VAR left: INTEGER := 0;
     this, right: INTEGER;
 BEGIN
   FOR i := FIRST(culture) TO LAST(culture) - 1 DO
     right := culture[i + 1];
     this := culture[i];
     culture[i] := 
         Word.Or(Word.And(this, Word.Xor(left, right)), Word.And(Word.Not(this), Word.And(left, right)));
     left := this;
   END;
   culture[LAST(culture)] := Word.And(culture[LAST(culture)], Word.Not(left));
 END Step;

PROCEDURE Put(VAR culture: ARRAY OF INTEGER) =

 BEGIN
   FOR i := FIRST(culture) TO LAST(culture) DO
     IF culture[i] = 1 THEN
       IO.PutChar('#');
     ELSE
       IO.PutChar('_');
     END;
   END;
 END Put;

BEGIN

 FOR i := 0 TO 9 DO
   IO.Put("Generation " & Fmt.Int(i) & " ");
   Put(culture);
   IO.Put("\n");
   Step(culture);
 END;

END Cell.</lang> Output:

Generation 0 _###_##_#_#_#_#__#__
Generation 1 _#_#####_#_#_#______
Generation 2 __##___##_#_#_______
Generation 3 __##___###_#________
Generation 4 __##___#_##_________
Generation 5 __##____###_________
Generation 6 __##____#_#_________
Generation 7 __##_____#__________
Generation 8 __##________________
Generation 9 __##________________

Nial

(life.nial) <lang nial>% we need a way to write a values and pass the same back wi is rest link [write, pass] % calculate the neighbors by rotating the array left and right and joining them neighbors is pack [pass, sum [-1 rotate, 1 rotate]] % calculate the individual birth and death of a single array element igen is fork [ = [ + [first, second], 3 first], 0 first, = [ + [first, second], 2 first], 1 first, 0 first ] % apply that to the array nextgen is each igen neighbors % 42 life is fork [ > [sum pass, 0 first], life nextgen wi, pass ]</lang> Using it <lang nial>|loaddefs 'life.nial' |I := [0,1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1,0,0] |life I</lang>

OCaml

<lang ocaml>let get g i =

 try g.(i)
 with _ -> 0

let next_cell g i =

 match get g (i-1), get g (i), get g (i+1) with
 | 0, 0, 0 -> 0
 | 0, 0, 1 -> 0
 | 0, 1, 0 -> 0
 | 0, 1, 1 -> 1
 | 1, 0, 0 -> 0
 | 1, 0, 1 -> 1
 | 1, 1, 0 -> 1
 | 1, 1, 1 -> 0
 | _ -> assert(false)

let next g =

 let old_g = Array.copy g in
 for i = 0 to pred(Array.length g) do
   g.(i) <- (next_cell old_g i)
 done

let print_g g =

 for i = 0 to pred(Array.length g) do
   if g.(i) = 0
   then print_char '_'
   else print_char '#'
 done;
 print_newline()</lang>

put the code above in a file named "life.ml", and then use it in the ocaml toplevel like this:

#use "life.ml" ;;

let iter n g =
  for i = 0 to n do
    Printf.printf "Generation %d: " i; print_g g;
    next g;
  done
;;

let g_of_string str =
  let f = (function '_' -> 0 | '#' -> 1 | _ -> assert false) in
  Array.init (String.length str) (fun i -> f str.[i])
;;

# iter 9 (g_of_string "_###_##_#_#_#_#__#__") ;;
Generation 0: _###_##_#_#_#_#__#__
Generation 1: _#_#####_#_#_#______
Generation 2: __##___##_#_#_______
Generation 3: __##___###_#________
Generation 4: __##___#_##_________
Generation 5: __##____###_________
Generation 6: __##____#_#_________
Generation 7: __##_____#__________
Generation 8: __##________________
Generation 9: __##________________
- : unit = ()

Python

<lang python>import random

printdead, printlive = '_#' maxgenerations = 10 cellcount = 20 offendvalue = '0'

universe = .join(random.choice('01') for i in range(cellcount))

neighbours2newstate = {

'000': '0',
'001': '0',
'010': '0',
'011': '1',
'100': '0',
'101': '1',
'110': '1',
'111': '0',
}

for i in range(maxgenerations):

   print "Generation %3i:  %s" % ( i,
         universe.replace('0', printdead).replace('1', printlive) )
   universe = offendvalue + universe + offendvalue
   universe = .join(neighbours2newstate[universe[i:i+3]] for i in range(cellcount))</lang>

Sample output:

Generation   0:  _###_##_#_#_#_#__#__
Generation   1:  _#_#####_#_#_#______
Generation   2:  __##___##_#_#_______
Generation   3:  __##___###_#________
Generation   4:  __##___#_##_________
Generation   5:  __##____###_________
Generation   6:  __##____#_#_________
Generation   7:  __##_____#__________
Generation   8:  __##________________
Generation   9:  __##________________

The following implementation uses boolean operations to realize the function.

<lang python>import random

nquads = 5 maxgenerations = 10 fmt = '%%0%ix'%nquads nbits = 4*nquads a = random.getrandbits(nbits) << 1

  1. a = int('01110110101010100100', 2) << 1

endmask = (2<<nbits)-2; endvals = 0<<(nbits+1) | 0 tr = ('____', '___#', '__#_', '__##', '_#__', '_#_#', '_##_', '_###',

     '#___', '#__#', '#_#_', '#_##', '##__', '##_#', '###_', '####' )

for i in range(maxgenerations):

  print "Generation %3i:  %s" % (i,(.join(tr[int(t,16)] for t in (fmt%(a>>1)))))
  a |= endvals
  a = ((a&((a<<1) | (a>>1))) ^ ((a<<1)&(a>>1))) & endmask</lang>

R

<lang R>set.seed(15797, kind="Mersenne-Twister")

maxgenerations = 10 cellcount = 20 offendvalue = FALSE

    1. Cells are alive if TRUE, dead if FALSE

universe <- c(offendvalue,

             sample( c(TRUE, FALSE), cellcount, replace=TRUE),
             offendvalue)
    1. List of patterns in which the cell stays alive

stayingAlive <- lapply(list(c(1,1,0),

                           c(1,0,1),
                           c(0,1,0)), as.logical)
    1. x : length 3 logical vector
    2. map: list of length 3 logical vectors that map to patterns
    3. in which x stays alive

deadOrAlive <- function(x, map) list(x) %in% map

cellularAutomata <- function(x, map) {

   c(x[1], apply(embed(x, 3), 1, deadOrAlive, map=map), x[length(x)])

}

deadOrAlive2string <- function(x) {

   paste(ifelse(x, '#', '_'), collapse="")

}

for (i in 1:maxgenerations) {

   universe <- cellularAutomata(universe, stayingAlive)
   cat(format(i, width=3), deadOrAlive2string(universe), "\n")

}</lang>

Sample output,

  1 _##_____####_#___#_#__ 
  2 _##_____#__##_____#___ 
  3 _##________##_________ 
  4 _##________##_________ 
  5 _##________##_________ 
  6 _##________##_________ 
  7 _##________##_________ 
  8 _##________##_________ 
  9 _##________##_________ 
 10 _##________##_________ 


Ruby

<lang ruby>def evolve(ary)

 new = Array.new(ary.length)
 new[0] = (ary[0] == 1 and ary[1] == 1) ? 1 : 0
 (1..new.length - 2).each {|i| new[i] = ary[i-1] + ary[i] + ary[i+1] == 2 ? 1 : 0}
 new[-1] = (ary[-2] == 1 and ary[-1] == 1) ? 1 : 0
 new

end

def printit(ary)

 s = ary.join("")
 s.gsub!(/1/,"#")
 s.gsub!(/0/,".")
 puts s

end

ary = [0,1,1,1,0,1,1,0,1,0,1,0,1,0,1,0,0,1,0,0] printit ary while ary != new=evolve(ary)

 printit new
 ary = new

end</lang>

.###.##.#.#.#.#..#..
.#.#####.#.#.#......
..##...##.#.#.......
..##...###.#........
..##...#.##.........
..##....###.........
..##....#.#.........
..##.....#..........
..##................

Tcl

<lang tcl>proc evolve {a} {

   set new [list]
   for {set i 0} {$i < [llength $a]} {incr i} {
       lappend new [fate $a $i]
   }
   return $new

}

proc fate {a i} {

   return [expr {[sum $a $i] == 2}]

}

proc sum {a i} {

   set sum 0
   set start [expr {$i - 1 < 0 ? 0 : $i - 1}]
   set end [expr {$i + 1 >= [llength $a] ? $i : $i + 1}]
   for {set j $start} {$j <= $end} {incr j} {
       incr sum [lindex $a $j]        
   }
   return $sum

}

proc print {a} {

   puts [string map {0 _ 1 #} [join $a ""]]

}

proc parse {s} {

   return [split [string map {_ 0 # 1} $s] ""]

}

set array [parse "_###_##_#_#_#_#__#__"] print $array while {[set new [evolve $array]] ne $array} {

   set array $new
   print $array

}</lang>

Ursala

Three functions are defined. Rule takes a neighborhood of three cells to the succeeding value of the middle one, step takes a list of cells to its successor by applying the rule across a sliding window, and evolve takes an initial list of cells to a list of those evolving from it according to the rule. The cells are maintained as a list of booleans (0 and &) but are converted to characters for presentation in the example code. <lang Ursala>#import std

  1. import nat

rule = -$<0,0,0,&,0,&,&,0>@rSS zipp0*ziD iota8

step = rule*+ swin3+ :/0+ --<0>

evolve "n" = @iNC ~&x+ rep"n" ^C/step@h ~&

  1. show+

example = ~&?(`#!,`.!)** evolve10 <0,&,&,&,0,&,&,0,&,0,&,0,&,0,0,&,0,0></lang> output:

.###.##.#.#.#..#..
.#.#####.#.#......
..##...##.#.......
..##...###........
..##...#.#........
..##....#.........
..##..............
..##..............
..##..............
..##..............
..##..............


Vedit macro language

This implementation writes the calculated patterns into an edit buffer, where the results can viewed and saved into a file if required. The edit buffer also acts as storage during calculations. <lang vedit>IT("Gen 0: ..###.##.#.#.#.#..#.....") // initial pattern

  1. 9 = Cur_Col

for (#8 = 1; #8 < 10; #8++) { // 10 generations

   Goto_Col(7)
   Reg_Empty(20)
   while (Cur_Col < #9-1) {
       if (Match("|{##|!#,#.#,|!###}")==0) {
           Reg_Set(20, "#", APPEND)
       } else {
           Reg_Set(20, ".", APPEND)
       }
       Char
   }
   EOL IN
   IT("Gen ") Num_Ins(#8, LEFT+NOCR) IT(": ")
   Reg_Ins(20)

}</lang>

Sample output: <lang vedit>Gen 0: ..###.##.#.#.#.#..#..... Gen 1: ..#.#####.#.#.#......... Gen 2: ...##...##.#.#.......... Gen 3: ...##...###.#........... Gen 4: ...##...#.##............ Gen 5: ...##....###............ Gen 6: ...##....#.#............ Gen 7: ...##.....#............. Gen 8: ...##................... Gen 9: ...##...................</lang>