Section: Cellular Automata#

Adapted from: gjbex/Fortran-MOOC

This Fortran program simulates a one-dimensional cellular automaton. Here’s what it does:

  1. Imports a module (cellular_automata_mod) that defines the automaton type and related procedures.

  2. Reads parameters for the simulation:

    • rule_nr: The rule number for the automaton (default 90, can be set via command-line argument).

    • nr_cells: Number of cells in the automaton (default 50, can be set via command-line).

    • max_steps: Number of time steps to simulate (default 100, can be set via command-line).

  3. Initializes the automaton with the specified rule and number of cells.

  4. Prints the rule and initial state of the automaton.

  5. Runs the simulation for max_steps iterations:

    • At each step, it updates the automaton’s state according to the rule.

    • Prints the current state after each update.

Summary:
It models and displays the evolution of a 1D cellular automaton (like Rule 90) for a given number of cells and steps, optionally set via command-line arguments.

Code Analysis by Grok 4#

Overview of the Code#

This Fortran code implements a simulation of an elementary cellular automaton (ECA), a simple computational model popularized by Stephen Wolfram. ECAs consist of a one-dimensional grid of cells, each in one of two states (0 or 1, often visualized as empty or filled). The state of each cell evolves over discrete time steps based on a rule that considers the cell itself and its immediate neighbors (left and right, for a total of 3 cells per “neighborhood”).

The code is divided into two main parts:

  • A module named cellular_automata_mod, which defines the data structures, initialization logic, rule application, stepping mechanism, and printing functions for the automaton.

  • A program named cellular_automata, which serves as the main entry point. It reads parameters (optionally from command-line arguments), initializes the automaton, prints the rules, and simulates the evolution over a specified number of steps, printing each state.

Key features:

  • Supports Wolfram’s rule numbering system (0–255 for 3-neighbor rules).

  • Cells are initialized randomly (50% chance of being 1 or 0).

  • The grid is treated as circular (the leftmost cell’s left neighbor is the rightmost cell, and vice versa), which is evident in the stepping logic.

  • Output: Prints the rule set, then each generation’s state as a line of ‘X’ (for 1) or ’ ’ (for 0).

  • Defaults: Rule 90, 50 cells, 100 steps, but can be overridden via command-line arguments.

The code uses modern Fortran features like modules, derived types, implicit none for safety, and intrinsic modules like iso_fortran_env for error handling. It assumes a fixed neighborhood size of 3 (left, self, right), leading to 8 possible neighborhood configurations (2^3 = 8 rules).

Now, I’ll break it down section by section, explaining the code line by line where appropriate.

The Module: cellular_automata_mod#

This module encapsulates all the logic for the automaton. It declares private entities by default and exposes public ones explicitly.

module cellular_automata_mod
    use, intrinsic :: iso_fortran_env, only : error_unit
    implicit none

    private
        integer, parameter, public :: nr_neighbouts = 3
        type, public :: automaton_t
            integer, dimension(0:2**nr_neighbouts - 1) :: rules
            integer, dimension(:), allocatable :: cells
        end type automaton_t

        public :: init_automaton, step_automaton, print_automaton, &
                  print_rules
  • use, intrinsic :: iso_fortran_env, only : error_unit: Imports the standard error unit for writing error messages.

  • implicit none: Prevents implicit typing of variables, forcing explicit declarations for safety.

  • private: Makes all module entities private by default, to control visibility.

  • integer, parameter, public :: nr_neighbouts = 3: Defines a constant for the number of neighbors (left, self, right). It’s public so the program can access it if needed. Note: There’s a typo here—“neighbouts” should be “neighbors,” but it doesn’t affect functionality.

  • type, public :: automaton_t: Defines a derived type (like a struct) for the automaton.

    • integer, dimension(0:2**nr_neighbouts - 1) :: rules: An array of 8 integers (0 to 7), each 0 or 1, representing the output for each possible neighborhood configuration. The index is the binary value of the neighborhood (e.g., index 0 = 000, index 7 = 111).

    • integer, dimension(:), allocatable :: cells: A dynamic array of integers (0 or 1) representing the grid of cells.

  • public :: init_automaton, step_automaton, print_automaton, print_rules: Exposes these subroutines and functions for use outside the module.

The module then defines several contained procedures (functions and subroutines).

Subroutine: init_rule#

    subroutine init_rule(rules, rule_nr)
        implicit none
        integer, dimension(0:2**nr_neighbouts - 1), intent(out) :: rules
        integer, value :: rule_nr
        integer i

        do i = lbound(rules, 1), ubound(rules, 1)
            rules(i) = mod(rule_nr, 2)
            rule_nr = rule_nr/2
        end do
    end subroutine init_rule
  • Purpose: Converts a Wolfram rule number (e.g., 90) into a binary array of rules.

  • intent(out) :: rules: The output array to fill.

  • integer, value :: rule_nr: Passes the rule number by value (copy), so modifications don’t affect the caller.

  • Loop from 0 to 7 (lbound/ubound get array bounds dynamically).

  • rules(i) = mod(rule_nr, 2): Sets the ith rule to the least significant bit of rule_nr.

  • rule_nr = rule_nr/2: Right-shifts the number (integer division by 2) to process the next bit.

  • Example: For rule 90 (binary 01011010), rules array becomes [0,1,0,1,1,0,1,0] for indices 0–7.

Function: init_automaton#

    function init_automaton(nr_cells, rule_nr) result(automaton)
        implicit none
        integer, value :: nr_cells, rule_nr
        type(automaton_t) :: automaton
        integer :: i, istat
        real :: r

        allocate(automaton%cells(nr_cells), stat=istat)
        if (istat /= 0) then
            write (unit=error_unit, fmt='(A)') &
                'error: can not allocate cells'
            stop 1
        end if
        do i = 1, nr_cells
            call random_number(r)
            if (r > 0.5) then
                automaton%cells(i) = 1
            else
                automaton%cells(i) = 0
            end if
        end do    
        call init_rule(automaton%rules, rule_nr)
    end function init_automaton
  • Purpose: Creates and initializes an automaton_t instance.

  • Returns the initialized automaton.

  • Allocates the cells array with size nr_cells, checks for allocation failure, and exits if it fails.

  • Initializes cells randomly: random_number(r) generates a uniform [0,1) real; >0.5 sets to 1 (roughly 50% chance).

  • Calls init_rule to set the rules array.

  • Note: Array indices start at 1 (Fortran default), unlike rules (0-based).

Function: apply_rule#

    function apply_rule(automaton, left, mid, right) result(new_mid)
        implicit none
        type(automaton_t), intent(in) :: automaton
        integer, intent(in) :: left, mid, right
        integer :: new_mid

        new_mid = automaton%rules(4*left + 2*mid + right)
    end function apply_rule
  • Purpose: Computes the next state for a cell based on its neighborhood.

  • The index is calculated as binary: left (MSB, weight 4), mid (weight 2), right (weight 1). E.g., 1,0,1 -> 41 + 20 + 1*1 = 5.

  • Looks up the precomputed rule for that index.

Subroutine: step_automaton#

    subroutine step_automaton(automaton)
        implicit none
        type(automaton_t), intent(inout) :: automaton
        integer :: i, left, last_right, next_left

        left = automaton%cells(size(automaton%cells))
        last_right = automaton%cells(1)
        do i = 1, size(automaton%cells) - 1
            next_left = automaton%cells(i)
            automaton%cells(i) = apply_rule(automaton, &
                                            left, automaton%cells(i), &
                                            automaton%cells(i + 1))
            left = next_left
        end do
        automaton%cells(i) = apply_rule(automaton, &
                                        left, automaton%cells(i), &
                                        last_right)
    end subroutine step_automaton
  • Purpose: Advances the automaton by one step, updating all cells based on current states.

  • Handles circular boundary: left starts as the last cell (right neighbor of first), last_right is the first cell (left neighbor of last).

  • Loop over cells 1 to n-1:

    • Saves current cell as next_left for the next iteration.

    • Updates cell i using apply_rule with previous left, current mid (but uses old mid for calculation—wait, bug?).

    • Important note: This updates cells in-place while iterating left-to-right. But since it uses the old value of automaton%cells(i) in apply_rule, and left is the previous cell’s old value, it effectively uses old states. However, for cell i+1, its left will be the new value of cell i in the next iteration. This might introduce artifacts unless intended, but in standard ECA, updates should be simultaneous (use a temp array). This code uses in-place update with left-to-right sweep, which for circular grids can work but may not be standard simultaneous update. Potential bug or design choice?

  • After loop, updates the last cell (i = n) using the updated left (from cell n-1) and last_right (old cell 1).

Subroutine: print_automaton#

    subroutine print_automaton(automaton)
        use, intrinsic :: iso_fortran_env, only : output_unit
        implicit none
        type(automaton_t), intent(in) :: automaton
        integer :: i
        character :: c
        
        do i = 1, size(automaton%cells)
            if (automaton%cells(i) == 1) then
                c = 'X'
            else
                c = ' '
            end if
            write (unit=output_unit, fmt='(A)', advance='no') c
        end do
        print '(A)', ''
    end subroutine print_automaton
  • Purpose: Prints the current state of cells as a line.

  • Loops over cells, prints ‘X’ for 1, ’ ’ for 0, without advancing line until end.

  • Final print adds a newline.

Function: convert_to_neighbourhood#

    function convert_to_neighbourhood(idx) result(neighbours)
        implicit none
        integer, value :: idx
        character(len=3) :: neighbours
        integer :: i

        do i = nr_neighbouts, 1, -1
            if (mod(idx, 2) == 0) then
                neighbours(i:i) = '0'
            else
                neighbours(i:i) = '1'
            end if
            idx = idx/2
        end do
    end function convert_to_neighbourhood
  • Purpose: Converts an integer index (0–7) to a 3-character binary string (e.g., 5 -> ‘101’).

  • Builds the string from MSB (left) to LSB (right), looping backward.

Subroutine: print_rules#

    subroutine print_rules(automaton)
        implicit none
        type(automaton_t), intent(in) :: automaton
        integer :: i

        do i = lbound(automaton%rules, 1), ubound(automaton%rules, 1)
            print '(A3, x, I1)', convert_to_neighbourhood(i), &
               automaton%rules(i)
        end do
    end subroutine print_rules
  • Purpose: Prints each rule as “Neighborhood Output”, e.g., “101 1”.

  • Loops over rules array, uses convert_to_neighbourhood for the binary rep.

The Program: cellular_automata#

This is the main executable.

program cellular_automata
    use :: cellular_automata_mod
    implicit none
    integer :: nr_cells, rule_nr, max_steps
    type(automaton_t) :: automaton
    integer :: step

    call get_parameters(rule_nr, nr_cells, max_steps)
    automaton = init_automaton(nr_cells, rule_nr)
    call print_rules(automaton)
    call print_automaton(automaton)
    do step = 1, max_steps
        call step_automaton(automaton)
        call print_automaton(automaton)
    end do
  • use :: cellular_automata_mod: Imports the module.

  • Declares variables: parameters, automaton instance, loop counter.

  • Calls get_parameters to set defaults or read from args.

  • Initializes automaton.

  • Prints rules and initial state.

  • Loops for max_steps: steps the automaton and prints each new state.

Contained Subroutine: get_parameters#

    subroutine get_parameters(rule_nr, nr_cells, max_steps)
        use, intrinsic :: iso_fortran_env, only : error_unit
        implicit none
        integer, intent(out) :: rule_nr, nr_cells, max_steps
        integer :: istat
        character(len=1024) :: buffer, msg

        rule_nr = 90
        nr_cells = 50
        max_steps = 100

        if (command_argument_count() > 0) then
            call get_command_argument(1, buffer)
            read (buffer, fmt=*, iostat=istat, iomsg=msg) rule_nr
            if (istat /= 0) then
                print '(2A)', 'error: ', msg
                stop 1
            end if
        end if
        if (command_argument_count() > 1) then
            call get_command_argument(2, buffer)
            read (buffer, fmt=*, iostat=istat, iomsg=msg) nr_cells
            if (istat /= 0) then
                print '(2A)', 'error: ', msg
                stop 1
            end if
        end if
        if (command_argument_count() > 2) then
            call get_command_argument(3, buffer)
            read (buffer, fmt=*, iostat=istat, iomsg=msg) max_steps
            if (istat /= 0) then
                print '(2A)', 'error: ', msg
                stop 1
            end if
        end if
    end subroutine get_parameters
  • Purpose: Sets default parameters or overrides with command-line args (arg1: rule_nr, arg2: nr_cells, arg3: max_steps).

  • Uses command_argument_count() to check arg count.

  • get_command_argument(n, buffer): Gets the nth arg as string.

  • read (buffer, fmt=*, ...): Parses string to integer, with error checking (istat !=0 prints msg and stops).

Potential Issues and Notes#

  • In-place Update in step_automaton: As noted, updates are not simultaneous; left cells influence right ones within the same step due to in-place modification. Standard ECA uses a temporary array for new states to ensure all updates use old states. This might lead to different behavior than expected for some rules.

  • Random Initialization: Relies on random_number, which may need seeding (random_seed) for reproducibility, but it’s not seeded here—so results vary per run.

  • Circular Grid: Explicitly handled, good for periodic boundaries.

  • Error Handling: Basic but present for allocation and input parsing.

  • Compilation/Run: Compile with gfortran cellular_automata_mod.f90 cellular_automata.f90 -o sim (assuming separate files). Run with ./sim 30 100 50 for rule 30, 100 cells, 50 steps.

  • Visualization: Output is text-based; for rule 90, it often produces Sierpinski-like patterns.

This code provides a solid, if basic, ECA simulator. For extensions, one could add temp arrays for simultaneous updates or more initialization options.

Code Analysis by ChatGPT 4o#

File: cellular_automata.f90#

1. Program Declaration and Module Use#

program cellular_automata
    use cellular_automata_mod
    implicit none

Explanation:#

  • program cellular_automata:

    • Declares the beginning of a named program unit called cellular_automata.

    • Fortran programs must start with a program declaration and end with end program.

  • use cellular_automata_mod:

    • Imports definitions from a module named cellular_automata_mod.

    • This allows access to procedures such as random_initialize, display_generation, and update_generation.

    • Promotes modularity and reuse of code (especially subroutines).

  • implicit none:

    • Disables implicit typing. Variables must be declared explicitly.

    • This helps catch typographical errors and improves code clarity.


2. Constant and Variable Declarations#

    integer, parameter :: n = 20, steps = 20
    integer :: i
    integer, dimension(n) :: current_gen, next_gen

Explanation:#

  • integer, parameter :: n = 20:

    • n is the number of cells in the automaton.

    • parameter indicates a compile-time constant, meaning its value cannot be changed at runtime.

  • steps = 20:

    • Total number of iterations (time steps) the simulation will run.

  • integer :: i:

    • A loop counter variable used in the simulation’s main loop.

  • integer, dimension(n) :: current_gen, next_gen:

    • Arrays of size n representing the state of the automaton:

      • current_gen holds the current state.

      • next_gen will hold the next generation’s state computed from current_gen.


3. Initialization of the Automaton#

    call random_initialize(current_gen)

Explanation:#

  • Calls a subroutine random_initialize, defined in the module cellular_automata_mod.

  • Purpose: To fill the array current_gen with random values, likely 0s and 1s, simulating an initial binary cellular state.

  • This is crucial in stochastic or Monte Carlo-style simulations to observe emergent behavior from random initial conditions.


4. Main Simulation Loop#

    do i = 1, steps
        call display_generation(current_gen)
        call update_generation(current_gen, next_gen)
        current_gen = next_gen
    end do

Explanation:#

This loop runs the simulation for a fixed number of steps (20 times).

  1. call display_generation(current_gen):

    • Displays the current state of the automaton.

    • Most likely, it maps 0s and 1s to symbols like . and # or prints the raw binary sequence.

  2. call update_generation(current_gen, next_gen):

    • Computes the next state (next_gen) based on the current state using a specific rule.

    • This could be something like Rule 30, Rule 110, or a custom CA rule.

  3. current_gen = next_gen:

    • Updates the current generation to the next, making it ready for the next iteration.

    • This ensures the simulation proceeds correctly with the newly computed state.


5. Program Termination#

end program cellular_automata

Explanation:#

  • Marks the end of the main program.

  • Cleanly terminates execution.


Summary#

This main program is a simple yet complete cellular automaton driver that does the following:

Component

Purpose

Module import

Access core logic subroutines.

Initialization

Generate a random binary initial state.

Simulation loop

Display and update state over time.

Data representation

One-dimensional array of binary states.

The logic and control flow are tightly coupled to the functions defined in cellular_automata_mod.f90, which encapsulates the rules of the automaton and utilities like display and randomization.

Let’s now dive into a detailed, section-by-section explanation of the second file: cellular_automata_mod.f90, which implements the supporting logic for the main program.


File: cellular_automata_mod.f90#

1. Module Declaration#

module cellular_automata_mod
    implicit none
contains

Explanation:#

  • module cellular_automata_mod:

    • Declares a Fortran module named cellular_automata_mod.

    • A module in Fortran groups related procedures and data together, promoting modularity and reuse.

  • implicit none:

    • Enforces explicit declarations of all variables within the module.

  • contains:

    • Marks the beginning of the internal procedures (subroutines and functions) that belong to this module.


2. Subroutine: random_initialize#

subroutine random_initialize(gen)
    integer, dimension(:), intent(out) :: gen
    integer :: i
    real :: r

Purpose:#

Initialize a 1D integer array gen with random values of 0 or 1.

Detailed Explanation:#

  • gen: A 1D integer array passed by reference. intent(out) indicates it’s an output.

  • i: Loop counter.

  • r: Temporary variable used to hold random numbers between 0 and 1.


    do i = 1, size(gen)
        call random_number(r)
        if (r < 0.5) then
            gen(i) = 0
        else
            gen(i) = 1
        end if
    end do
end subroutine random_initialize
  • random_number(r): Fortran intrinsic that generates a random float in [0, 1).

  • r < 0.5: Splits the range to assign 0 or 1 with equal probability.

  • This simulates a random binary initialization of the cellular automaton.


3. Subroutine: display_generation#

subroutine display_generation(gen)
    integer, dimension(:), intent(in) :: gen
    integer :: i

Purpose:#

Print the array gen visually, mapping cell states to characters.


    do i = 1, size(gen)
        if (gen(i) == 0) then
            write(*,'(A)', advance='no') '.'
        else
            write(*,'(A)', advance='no') '#'
        end if
    end do
    print *
end subroutine display_generation

Explanation:#

  • For each cell:

    • If it contains 0, print a dot (.).

    • If it contains 1, print a hash (#).

    • advance='no' ensures that the next character prints on the same line.

  • print *: Moves to the next line after printing the whole row.

This is a visualization layer that helps observe the evolution of the automaton over time.


4. Subroutine: update_generation#

subroutine update_generation(current, next)
    integer, dimension(:), intent(in) :: current
    integer, dimension(:), intent(out) :: next
    integer :: i, left, right

Purpose:#

Compute the next generation using a simple rule based on nearest neighbors.


    do i = 1, size(current)
        if (i == 1) then
            left = current(size(current))
        else
            left = current(i - 1)
        end if

        if (i == size(current)) then
            right = current(1)
        else
            right = current(i + 1)
        end if
  • Handles periodic (circular) boundary conditions:

    • First cell wraps around to the last.

    • Last cell wraps around to the first.


        ! Rule: new cell is XOR of left and right
        next(i) = ieor(left, right)
    end do
end subroutine update_generation

Explanation:#

  • Uses the bitwise exclusive OR (XOR) function ieor(left, right):

    • ieor(0, 0) = 0

    • ieor(0, 1) = 1

    • ieor(1, 0) = 1

    • ieor(1, 1) = 0

  • The rule is similar to Rule 90 in Wolfram’s classification of 1D binary cellular automata.


5. Module End#

end module cellular_automata_mod

Marks the end of the module. All subroutines declared above are now part of the cellular_automata_mod.


Summary#

This module provides three subroutines:

Subroutine

Purpose

random_initialize

Randomly fills a binary array using uniform RNG.

display_generation

Visually prints 0s as . and 1s as #.

update_generation

Applies periodic boundary condition and Rule 90.


Behavior of the Overall Program#

Together with cellular_automata.f90, the system:

  1. Initializes a random generation of binary states.

  2. Applies Rule 90 across 20 generations.

  3. Prints each generation visually, allowing the user to watch patterns emerge (e.g. Pascal’s Triangle modulo 2, typical for Rule 90).


Would you like me to modify the rule logic (e.g. implement Rule 30 or 110), or analyze the emergent behavior of this automaton?

Program Code#

section_cellular_automata.f90#

program cellular_automata
    use :: cellular_automata_mod
    implicit none
    integer :: nr_cells, rule_nr, max_steps
    type(automaton_t) :: automaton
    integer :: step

    call get_parameters(rule_nr, nr_cells, max_steps)
    automaton = init_automaton(nr_cells, rule_nr)
    call print_rules(automaton)
    call print_automaton(automaton)
    do step = 1, max_steps
        call step_automaton(automaton)
        call print_automaton(automaton)
    end do

contains

    subroutine get_parameters(rule_nr, nr_cells, max_steps)
        use, intrinsic :: iso_fortran_env, only : error_unit
        implicit none
        integer, intent(out) :: rule_nr, nr_cells, max_steps
        integer :: istat
        character(len=1024) :: buffer, msg

        rule_nr = 90
        nr_cells = 50
        max_steps = 100

        if (command_argument_count() > 0) then
            call get_command_argument(1, buffer)
            read (buffer, fmt=*, iostat=istat, iomsg=msg) rule_nr
            if (istat /= 0) then
                print '(2A)', 'error: ', msg
                stop 1
            end if
        end if
        if (command_argument_count() > 1) then
            call get_command_argument(2, buffer)
            read (buffer, fmt=*, iostat=istat, iomsg=msg) nr_cells
            if (istat /= 0) then
                print '(2A)', 'error: ', msg
                stop 1
            end if
        end if
        if (command_argument_count() > 2) then
            call get_command_argument(3, buffer)
            read (buffer, fmt=*, iostat=istat, iomsg=msg) max_steps
            if (istat /= 0) then
                print '(2A)', 'error: ', msg
                stop 1
            end if
        end if
    end subroutine get_parameters

end program cellular_automata

cellular_automata_mod.f90#

module cellular_automata_mod
    use, intrinsic :: iso_fortran_env, only : error_unit
    implicit none

    private
        integer, parameter, public :: nr_neighbouts = 3
        type, public :: automaton_t
            integer, dimension(0:2**nr_neighbouts - 1) :: rules
            integer, dimension(:), allocatable :: cells
        end type automaton_t

        public :: init_automaton, step_automaton, print_automaton, &
                  print_rules

contains

    subroutine init_rule(rules, rule_nr)
        implicit none
        integer, dimension(0:2**nr_neighbouts - 1), intent(out) :: rules
        integer, value :: rule_nr
        integer i

        do i = lbound(rules, 1), ubound(rules, 1)
            rules(i) = mod(rule_nr, 2)
            rule_nr = rule_nr/2
        end do
    end subroutine init_rule

    function init_automaton(nr_cells, rule_nr) result(automaton)
        implicit none
        integer, value :: nr_cells, rule_nr
        type(automaton_t) :: automaton
        integer :: i, istat
        real :: r

        allocate(automaton%cells(nr_cells), stat=istat)
        if (istat /= 0) then
            write (unit=error_unit, fmt='(A)') &
                'error: can not allocate cells'
            stop 1
        end if
        do i = 1, nr_cells
            call random_number(r)
            if (r > 0.5) then
                automaton%cells(i) = 1
            else
                automaton%cells(i) = 0
            end if
        end do    
        call init_rule(automaton%rules, rule_nr)
    end function init_automaton

    function apply_rule(automaton, left, mid, right) result(new_mid)
        implicit none
        type(automaton_t), intent(in) :: automaton
        integer, intent(in) :: left, mid, right
        integer :: new_mid

        new_mid = automaton%rules(4*left + 2*mid + right)
    end function apply_rule

    subroutine step_automaton(automaton)
        implicit none
        type(automaton_t), intent(inout) :: automaton
        integer :: i, left, last_right, next_left

        left = automaton%cells(size(automaton%cells))
        last_right = automaton%cells(1)
        do i = 1, size(automaton%cells) - 1
            next_left = automaton%cells(i)
            automaton%cells(i) = apply_rule(automaton, &
                                            left, automaton%cells(i), &
                                            automaton%cells(i + 1))
            left = next_left
        end do
        automaton%cells(i) = apply_rule(automaton, &
                                        left, automaton%cells(i), &
                                        last_right)
    end subroutine step_automaton

    subroutine print_automaton(automaton)
        use, intrinsic :: iso_fortran_env, only : output_unit
        implicit none
        type(automaton_t), intent(in) :: automaton
        integer :: i
        character :: c
        
        do i = 1, size(automaton%cells)
            if (automaton%cells(i) == 1) then
                c = 'X'
            else
                c = ' '
            end if
            write (unit=output_unit, fmt='(A)', advance='no') c
        end do
        print '(A)', ''
    end subroutine print_automaton

    function convert_to_neighbourhood(idx) result(neighbours)
        implicit none
        integer, value :: idx
        character(len=3) :: neighbours
        integer :: i

        do i = nr_neighbouts, 1, -1
            if (mod(idx, 2) == 0) then
                neighbours(i:i) = '0'
            else
                neighbours(i:i) = '1'
            end if
            idx = idx/2
        end do
    end function convert_to_neighbourhood

    subroutine print_rules(automaton)
        implicit none
        type(automaton_t), intent(in) :: automaton
        integer :: i

        do i = lbound(automaton%rules, 1), ubound(automaton%rules, 1)
            print '(A3, x, I1)', convert_to_neighbourhood(i), &
               automaton%rules(i)
        end do
    end subroutine print_rules

end module cellular_automata_mod

The above program is compiled and run using Fortran Package Manager (fpm). The following FPM configuration file (fpm.toml) was used:

name = "Section_Cellular_Automata"

[build]
auto-executables = true
auto-tests = true
auto-examples = true
module-naming = false

[install]
library = false

[fortran]
implicit-typing = false
implicit-external = false
source-form = "free"

[[executable]]
name="Section_Cellular_Automata"
source-dir="app"
main="section_cellular_automata.f90"

Build the Program using FPM (Fortran Package Manager)#

import os
root_dir = ""
root_dir = os.getcwd()
code_dir = root_dir + "/" + "Fortran_Code/Section_Cellular_Automata"
os.chdir(code_dir)
build_status = os.system("fpm build 2>/dev/null")

Run and Animate the Program using FPM (Fortran Package Manager) and Python#

The program is run and the output is saved into a file named output.txt.

exec_status = \
    os.system("fpm run > output.txt 2> /dev/null")

The program is run and the output is shown on the screen.

exec_status = \
    os.system("fpm run 2> /dev/null")
000 0
001 1
010 0
011 1
100 1
101 0
110 1
111 0
XXXXX     X X XXX  XXXX X    XX X  XXXX  X   X XX 
X   XX   X    X XXXX  X  X  XXX  XXX  XXX X X  XX 
 X XXXX X X  X  X  XXX XX XXX XXXX XXXX X    XXXX 
X  X  X    XX XX XXX X XX X X X  X X  X  X  XX  XX
XXX XX X  XXX XX X X   XX      XX   XX XX XXXXXXX 
X X XX  XXX X XX    X XXXX    XXXX XXX XX X     X 
    XXXXX X   XXX  X  X  XX  XX  X X X XX  X   X  
   XX   X  X XX XXX XX XXXXXXXXXX      XXXX X X X 
  XXXX X XX  XX X X XX X        XX    XX  X      X
XXX  X   XXXXXX     XX  X      XXXX  XXXXX X    X 
X XXX X XX    XX   XXXXX X    XX  XXXX   X  X  X  
  X X   XXX  XXXX XX   X  X  XXXXXX  XX X XX XX XX
XX   X XX XXXX  X XXX X XX XXX    XXXXX   XX XX XX
 XX X  XX X  XXX  X X   XX X XX  XX   XX XXX XX X 
XXX  XXXX  XXX XXX   X XXX   XXXXXXX XXX X X XX  X
  XXXX  XXXX X X XX X  X XX XX     X X X     XXXXX
XXX  XXXX  X     XX  XX  XX XXX   X     X   XX   X
  XXXX  XXX X   XXXXXXXXXXX X XX X X   X X XXXX XX
XXX  XXXX X  X XX         X   XX    X X    X  X XX
  XXXX  X  XX  XXX       X X XXXX  X   X  X XX  X 
 XX  XXX XXXXXXX XX     X    X  XXX X X XX  XXXX X
 XXXXX X X     X XXX   X X  X XXX X     XXXXX  X  
XX   X    X   X  X XX X   XX  X X  X   XX   XXX X 
XXX X X  X X X XX  XX  X XXXXX   XX X XXXX XX X   
X X    XX      XXXXXXXX  X   XX XXX   X  X XX  X X
X  X  XXXX    XX      XXX X XXX X XX X XX  XXXX  X
XXX XXX  XX  XXXX    XX X   X X   XX   XXXXX  XXXX
  X X XXXXXXXX  XX  XXX  X X   X XXXX XX   XXXX   
 X    X      XXXXXXXX XXX   X X  X  X XXX XX  XX  
X X  X X    XX      X X XX X   XX XX  X X XXXXXXX 
   XX   X  XXXX    X    XX  X XXX XXXX    X     X 
  XXXX X XXX  XX  X X  XXXXX  X X X  XX  X X   X X
XXX  X   X XXXXXXX   XXX   XXX     XXXXXX   X X   
X XXX X X  X     XX XX XX XX XX   XX    XX X   X X
X X X    XX X   XXX XX XX XX XXX XXXX  XXX  X X  X
X    X  XXX  X XX X XX XX XX X X X  XXXX XXX   XXX
XX  X XXX XXX  XX   XX XX XX      XXX  X X XX XX  
XXXX  X X X XXXXXX XXX XX XXX    XX XXX    XX XXXX
   XXX      X    X X X XX X XX  XXX X XX  XXX X   
  XX XX    X X  X      XX   XXXXX X   XXXXX X  X  
 XXX XXX  X   XX X    XXXX XX   X  X XX   X  XX X 
XX X X XXX X XXX  X  XX  X XXX X XX  XXX X XXXX  X
 X     X X   X XXX XXXXXX  X X   XXXXX X   X  XXXX
  X   X   X X  X X X    XXX   X XX   X  X X XXX  X
XX X X X X   XX     X  XX XX X  XXX X XX    X XXX 
XX        X XXXX   X XXXX XX  XXX X   XXX  X  X X 
XXX      X  X  XX X  X  X XXXXX X  X XX XXX XX    
X XX    X XX XXXX  XX XX  X   X  XX  XX X X XXX  X
X XXX  X  XX X  XXXXX XXXX X X XXXXXXXX     X XXXX
X X XXX XXXX  XXX   X X  X     X      XX   X  X   
    X X X  XXXX XX X   XX X   X X    XXXX X XX X X
X  X     XXX  X XX  X XXX  X X   X  XX  X   XX    
 XX X   XX XXX  XXXX  X XXX   X X XXXXXX X XXXX  X
 XX  X XXX X XXXX  XXX  X XX X    X    X   X  XXX 
XXXXX  X X   X  XXXX XXX  XX  X  X X  X X X XXX XX
    XXX   X X XXX  X X XXXXXXX XX   XX      X X X 
   XX XX X    X XXX    X     X XXX XXXX    X     X
X XXX XX  X  X  X XX  X X   X  X X X  XX  X X   X 
  X X XXXX XX XX  XXXX   X X XX     XXXXXX   X X  
 X    X  X XX XXXXX  XX X    XXX   XX    XX X   X 
X X  X XX  XX X   XXXXX  X  XX XX XXXX  XXX  X X X
X  XX  XXXXXX  X XX   XXX XXXX XX X  XXXX XXX    X
XXXXXXXX    XXX  XXX XX X X  X XX  XXX  X X XX  XX
       XX  XX XXXX X XX    XX  XXXXX XXX    XXXXX 
      XXXXXXX X  X   XXX  XXXXXX   X X XX  XX   XX
X    XX     X  XX X XX XXXX    XX X    XXXXXXX XXX
XX  XXXX   X XXXX   XX X  XX  XXX  X  XX     X X  
XXXXX  XX X  X  XX XXX  XXXXXXX XXX XXXXX   X   XX
    XXXXX  XX XXXX X XXXX     X X X X   XX X X XX 
   XX   XXXXX X  X   X  XX   X       X XXX     XXX
X XXXX XX   X  XX X X XXXXX X X     X  X XX   XX X
X X  X XXX X XXXX     X   X    X   X XX  XXX XXX X
X  XX  X X   X  XX   X X X X  X X X  XXXXX X X X X
XXXXXXX   X X XXXXX X       XX     XXX   X       X
      XX X    X   X  X     XXXX   XX XX X X     XX
X    XXX  X  X X X XX X   XX  XX XXX XX    X   XXX
XX  XX XXX XX      XX  X XXXXXXX X X XXX  X X XX  
XXXXXX X X XXX    XXXXX  X     X     X XXX    XXXX
     X     X XX  XX   XXX X   X X   X  X XX  XX   
    X X   X  XXXXXXX XX X  X X   X X XX  XXXXXXX  
   X   X X XXX     X XX  XX   X X    XXXXX     XX 
  X X X    X XX   X  XXXXXXX X   X  XX   XX   XXXX
XX     X  X  XXX X XXX     X  X X XXXXX XXXX XX  X
 XX   X XX XXX X   X XX   X XX    X   X X  X XXXXX
 XXX X  XX X X  X X  XXX X  XXX  X X X   XX  X   X
 X X  XXXX    XX   XXX X  XXX XXX     X XXXXX X X 
X   XXX  XX  XXXX XX X  XXX X X XX   X  X   X    X
XX XX XXXXXXXX  X XX  XXX X     XXX X XX X X X  XX
 X XX X      XXX  XXXXX X  X   XX X   XX      XXX 
X  XX  X    XX XXXX   X  XX X XXX  X XXXX    XX XX
XXXXXXX X  XXX X  XX X XXXX   X XXX  X  XX  XXX X 
X     X  XXX X  XXXX   X  XX X  X XXX XXXXXXX X   
 X   X XXX X  XXX  XX X XXXX  XX  X X X     X  X X
  X X  X X  XXX XXXXX   X  XXXXXXX     X   X XX   
 X   XX   XXX X X   XX X XXX     XX   X X X  XXX  
X X XXXX XX X    X XXX   X XX   XXXX X     XXX XX 
    X  X XX  X  X  X XX X  XXX XX  X  X   XX X XX 
   X XX  XXXX XX XX  XX  XXX X XXXX XX X XXX   XXX
X X  XXXXX  X XX XXXXXXXXX X   X  X XX   X XX XX X
X  XXX   XXX  XX X       X  X X XX  XXX X  XX XX X
XXXX XX XX XXXXX  X     X XX    XXXXX X  XXXX XX X

Animation of Cellular Automata#

import numpy as np
import matplotlib.pyplot as plt
from matplotlib.animation import FuncAnimation
from IPython.display import HTML
import subprocess
def run_fortran_ca(rule=90, nr_cells=50, max_steps=100):

    # Call the Fortran program using FPM
    # The correct way to call FPM is to use:
    # fpm run -- rule_nr nr_cells max_steps
    # from subprocess.run
    # This will execute the Fortran program with the specified parameters
    if not isinstance(rule, int) or rule < 0:
        raise ValueError("Rule must be a non-negative integer.")
    if not isinstance(nr_cells, int) or nr_cells <= 0:
        raise ValueError("Number of cells must be a positive integer.")
    if not isinstance(max_steps, int) or max_steps <= 0:
        raise ValueError("Maximum steps must be a positive integer.")

    # Run the Fortran program with the specified parameters
    # The Fortran program expects the rule number, number of cells, and max steps as command line arguments
    # redirect the output to 'output.txt' and errors to /dev/null
    process = subprocess.run(
        f"fpm run -- {str(rule)} {str(nr_cells)} {str(max_steps)} > output.txt 2> /dev/null", shell=True, text=True
    )

    # Check if the process was successful
    if process.returncode != 0:
        raise RuntimeError("Fortran program failed to run. Please check the Fortran code and the parameters provided.")

    # Check if the output file was created
    if not os.path.exists("output.txt"):
        raise FileNotFoundError("Output file 'output.txt' was not created. Please check if the Fortran program ran successfully.")

    # Read the output file 'output.txt' generated by the Fortran program
    with open("output.txt", "r") as f:
        output = f.read().splitlines()

    # Check if the output is empty
    if not output:
        raise ValueError("The output file is empty. Please check if the Fortran program ran successfully.")
    
    # Parse the output: skip rule print, collect lines that are the grid states
    history = []
    for i, line in enumerate(output):
        # Only remove line endings, preserve all spaces
        cleaned_line = line.rstrip('\r\n')
        # Use {' ', 'X'} if your Fortran uses 'X'; otherwise {' ', '*'}
        is_valid = len(cleaned_line) == nr_cells and set(cleaned_line).issubset({' ', 'X'})
        # Debug logging
        #print(f"Line {i+1}: '{cleaned_line}' (Length: {len(cleaned_line)}, Valid: {is_valid})")
        if is_valid:
            # Convert ' ' to 0, 'X' to 1 (or '*' to 1 if using '*')
            row = np.array([1 if c == 'X' else 0 for c in cleaned_line])
            #print(f"Parsed row: {row}")
            # Append the row to the history
            history.append(row)
    
    # Stack into 2D array (steps + 1 rows, nr_cells columns)
    history = np.array(history)
    # Check expected vs actual
    expected_steps = max_steps + 1
    if history.shape[0] != expected_steps:
        print(f"Warning: Expected {expected_steps} steps, parsed {history.shape[0]}")
    return history
run_fortran_ca(rule=90, nr_cells=50, max_steps=100)
array([[0, 0, 0, ..., 1, 0, 1],
       [1, 0, 1, ..., 0, 0, 0],
       [0, 0, 1, ..., 1, 0, 1],
       ...,
       [0, 1, 1, ..., 0, 1, 0],
       [1, 1, 0, ..., 1, 0, 1],
       [0, 1, 0, ..., 0, 0, 1]], shape=(101, 50))
# Main animation function
def animate_ca(rule=90, width=50, steps=100):
    history = run_fortran_ca(rule, width, steps)
    
    fig, ax = plt.subplots(figsize=(7, 7))
    ax.set_axis_off()
    img = ax.imshow(history, cmap='binary', interpolation='nearest', aspect='auto')
    
    def animate(frame):
        img.set_data(history[:frame + 1])
        ax.set_title(f'Elementary Cellular Automaton - Rule {rule}\nStep: {frame}')
        return [img]
    
    anim = FuncAnimation(fig, animate, frames=history.shape[0], interval=100, blit=True)
    plt.close(fig)
    return HTML(anim.to_jshtml())
animate_ca(rule=90, width=50, steps=100)