RATFOR & FLECS - Emirp primes

For the final post in this series, let’s write a real program in RATFOR and FLECS and see how they compare with the original FORTRAN. We’ll be implementing the reverse-primes emirp program we did before.

FLECS version

C     FLECS PROGRAM TO DISPLAY EMIRPS
C
C     *** TEST IF A NUMBER IS PRIME ***
      LOGICAL FUNCTION PRIME(N)
      INTEGER N
C     DEAL WITH NUMBERS <= 3
      IF (N .LE. 1) GOTO 200
      IF (N .EQ. 2 .OR. N .EQ. 3) GOTO 100
C     CHECK IF DIVISIBLE BY 2 OR 3
      IF (MOD(N,2) .EQ. 0) GOTO 200
      IF (MOD(N,3) .EQ. 0) GOTO 200
C     SEE IF DIVISIBLE BY 5, 7, ..., UP TO APPROX SQRT(N)
      DO (I=5,999999,2)
      IF (I*I .GT. N) GOTO 100
      IF (MOD(N,I) .EQ. 0) GOTO 200
      FIN
 100  PRIME = .TRUE.
      RETURN
 200  PRIME = .FALSE.
      RETURN
      END
C
C     *** REVERSE AN INTEGER'S DIGITS ***
      INTEGER FUNCTION REVRSE(N)
      INTEGER N
      INTEGER M,R
C     M IS COPY OF N FROM WHICH WE TAKE DIGITS
C     R IS REVERSED DIGITS
      M = N
      R = 0
C     LOOP UNTIL NO MORE DIGITS
      UNTIL (M .LT. 1)
C     TAKE LAST DIGIT FROM M AND APPEND TO R
      R = R * 10
      R = R + MOD(M, 10)
      M = M / 10
      FIN
      REVRSE = R
      RETURN
      END
C
C     *** TEST IF AN INTEGER IS AN EMIRP ***
      LOGICAL FUNCTION EMIRP(N)
      INTEGER N
C     EXTERNAL FUNCTIONS
      INTEGER REVRSE
      LOGICAL PRIME
C     R CONTAINS REVERSED DIGITS OF N
      INTEGER R
      R = REVRSE(N)
C     N AND R MUST BOTH BE PRIME AND NOT THE SAME VALUE
      IF (N .NE. R)
      IF (PRIME(N))
      IF (PRIME(R))
      EMIRP = .TRUE.
      RETURN
      FIN
      FIN
      FIN
      EMIRP = .FALSE.
      RETURN
      END
C
C     *** DISPLAY AN INTEGER ***
      SUBROUTINE SHOW(N)
      INTEGER N
      WRITE(6,50) N
 50   FORMAT(I10)
      RETURN
      END
C
C
C     *** MAIN ENTRY POINT ***
C     I IS COUNT OF EMIRPS FOUND
C     N IS NUMBER TO TEST
C     EXTERNAL FUNCTION
      LOGICAL EMIRP
      INTEGER I,N
      TEST-1
      TEST-2
      TEST-3
      STOP
C
C     *** SHOW FIRST 20 EMIRPS ***
      TO TEST-1
      N = 0
      I = 0
      WHILE (I .LT. 20)
      N = N + 1
      IF (EMIRP(N))
      CALL SHOW(N)
      I = I + 1
      FIN
      FIN
      FIN
C
C     *** SHOW EMIRPS BETWEEN 7,700 AND 8,000 ***
      TO TEST-2
      DO (N=7700,8000)
      IF (EMIRP(N)) CALL SHOW(N)
      FIN
      FIN
C
C     *** SHOW 10,000TH EMIRP ***
      TO TEST-3
      N = 0
      DO (I=1,10000)
      REPEAT UNTIL (EMIRP(N)) N = N + 1
      FIN
      CALL SHOW(N)
      FIN
C
      END

Apart from the FORMAT specification and the PRIME function we’ve eliminated all line numbers. PRIME could be written without line numbers but with the multiple paths out of the function that would need their own RETURN I think it’s better this way.

The internal procedures come in handy, eliminating the need for subroutines for TEST1-3, though this does make N and I global which makes me a little uneasy if this was a larger program.

We use the block structure often, with UNTIL, WHILE and REPEAT ... UNTIL; this simplifies code, though without indentation it’s a little hard to follow; the output of the preprocessor is useful here to show what it thinks the indentation should be, for example:

  86           TO TEST-1
  87           .  N = 0
  88           .  I = 0
  89           .  WHILE (I .LT. 20)
  90           .  .  N = N + 1
  91           .  .  IF (EMIRP(N))
  92           .  .  .  CALL SHOW(N)
  93           .  .  .  I = I + 1
  94           .  .  ...FIN
  95           .  ...FIN
  96           ...FIN

The compiler diagnostics also helped a lot with catching errors with missing FINs.

RATFOR

Now let’s try writing the RATFOR version.

######################################################################
# Ratfor program to display emirps
######################################################################

######### Test if a number is prime #########
logical function prime(n)
    integer n  # Number to test

    # Deal with numbers <= 3
    if (n < 1) goto 200
    if (n == 2 | n == 3) goto 100

    # Check if divisible by 2 or 3
    if (mod(n,2) == 0) goto 200
    if (mod(n,3) == 0) goto 200
      
    # See if divisible by 5, 7, ..., up to approx sqrt(n)
    for (i = 5; i < 1000000; i = i + 2) {
        if (I*I > n) goto 100
        if (mod(n,i) == 0) goto 200
    }

 100  prime = .true.
      return
 200  prime = .false.
      return
end

######### Reverse an integer's digits #########
integer function revrse(n)
    integer n  # Number to reverse
    integer m  # Copy of n from which we take digits
    integer r  # Reversed digits
    m = n
    r = 0
    while (m >= 1) {
        # Take last digit from m and append to r
        r = r * 10
        r = r + mod(m, 10)
        m = m / 10
    }
    revrse = r
    return
end

######### Test if an integer is an emirp #########
logical function emirp(n)
    integer n       # Number to test
    integer revrse  # External function
    logical prime   # External function
    integer r       # Reversed digits of n
    r = revrse(n)
    emirp = .false.
    # n and r must both be prime and not the same value
    if (n .ne. r & prime(n) & prime(r)) {
        emirp = .true.
    }
    return
end

######### Display an integer #########
subroutine show(n)
    integer n
    write(6,50) n
50  format(i10)
    return
end

######### Show first 20 emirps #########
subroutine test1
    logical emirp   # External function
    integer i       # Count of emirps found
    integer n       # Number to test
    n = 0
    for (i = 1; i <= 20; i = i + 1) {
        repeat {
            n = n + 1
        } until (emirp(n))
        call show(n)
    }
    return
end

######### Show emirps between 7,700 and 8,000 #########
subroutine test2
    logical emirp   # External function
    integer n       # Number to test
    for (n = 7700; n <= 8000; n = n + 1) {
        if (emirp(n)) {
            call show(n)
        }
    }
    return
end

######### Show 10,000th emirp #########
subroutine test3
    logical emirp   # External function
    integer i       # Count of emirps found
    integer n       # Number to test
    n = 0
    for (i = 1; i <= 10000; i = i + 1) {
        repeat {
            n = n + 1
        } until (emirp(n))
    }
    call show(n)
    return
end

######### Main entry point #########
call test1
call test2
call test3
stop
end

I feel right at home with the braces and the C style for loops, though I miss the increment operator ++. prime would be much better if I could just return (.true.) but that does not work on the version of RATFOR on MTS so we keep the line numbers and gotos.

With the above, plus the free form input (which was supported on MTS FORTRAN anyway) and the operators like < it was easy to write. However, I got precisely zero diagnostics from the RATFOR preprocessor, with all my typos caught by the FORTRAN compiler, from which I’d have to find the problem in the original source. Easy enough in a small program but would be painful in larger ones.

Final thoughts

RATFOR and FLECS both make writing FORTRAN easier and more pleasant at the cost of an extra step in the development process, and I found both succeed at that. RATFOR is clearer and easier to get started with (especially coming from a C background today); the implementation is almost aggressively simple, as the authors admit in their paper, and I wonder how well it would scale for writing larger programs. FLECS has a more robust implementation but a more diffuse design, such as two versions of switch; features like printing a neatly indented output would certainly help on MTS or its contemporaries but the language lacks the cosmetic features that make RATFOR easier to read.

Neither are much used today; FORTRAN 77 and beyond took some of these ideas and built them into the core language. The idea of translating a richer language into a widely used but less expressive language is still alive though: think of Coffeescript or Typescript producing Javascript.

Further information

Full source code for these programs can be found on github.

Comments

comments powered by Disqus