One-dimensional cellular automata

Revision as of 03:50, 24 October 2008 by rosettacode>NevilleDNZ (→‎Using high level BOOL arrays: fix random universe)

One dimensional cellular automata

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

<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; </ada> 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

INT upb generation = 10;
FORMAT alive or dead = $b("#","_")$;
 
BITS universe := 2r01110110101010100100;
   # universe := BIN ( ENTIER ( random * max int ) ); #
INT universe width = 20;
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 WHILE
  printf(($"Generation "9szd": "$, generation,
         $f(alive or dead)$, []BOOL(universe)[lwb universe:upb universe],
         $l$));
# WHILE # generation < upb 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

Using high level BOOL arrays

INT upb generation = 10;
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 WHILE
  printf(($"Generation "9szd": "$, generation,
         $f(alive or dead)$, universe,
         $l$));
# WHILE # generation < upb 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

Output:

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

BASIC

Works with: QuickBasic version 4.5
Translation of: Java

<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</qbasic> Output:

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

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

Some output:

*Life1D> mapM_ print . lahmahgaan $ "_###_##_#_#_#_#__#__"
"_###_##_#_#_#_#__#__"
"_#_#####_#_#_#______"
"__##___##_#_#_______"
"__##___###_#________"
"__##___#_##_________"
"__##____###_________"
"__##____#_#_________"
"__##_____#__________"
"__##________________"
 
*Life1D> main
"__##_##__#____###__#__#_______#_#_##"
"__#####_______#_#______________#_###"
"__#___#________#________________##_#"
"________________________________###_"
"________________________________#_#_"
"_________________________________#__"
"____________________________________"

J

life1d=: '_#'{~]@(([:3&(2=+/\)0,],0:)^:a:)

Example use:

   life1d ? 20 # 2
_###_##_#_#_#_#__#__
_#_#####_#_#_#______
__##___##_#_#_______
__##___###_#________
__##___#_##_________
__##____###_________
__##____#_#_________
__##_____#__________
__##________________

Java

This example requires a starting generation of at least length two (which is what you need for anything interesting anyway). <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(lastGen.length() - 2) == '#' ? 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; } }</java> Output:

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

Python

<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))

</python> 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.

<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</python>

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.

IT("Gen 0: ..###.##.#.#.#.#..#.....")     // initial pattern
#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)
}

Sample output:

Gen 0: ..###.##.#.#.#.#..#.....
Gen 1: ..#.#####.#.#.#.........
Gen 2: ...##...##.#.#..........
Gen 3: ...##...###.#...........
Gen 4: ...##...#.##............
Gen 5: ...##....###............
Gen 6: ...##....#.#............
Gen 7: ...##.....#.............
Gen 8: ...##...................
Gen 9: ...##...................