Code that baffles me. Could someone please explain?

Following code completely baffles me. Could someone please give me a line by line explanation? Many thanks in advance. Patrick.

   CHARACTER S*6 / '987654' /, T*6 
   INTEGER V(3)*4 
   DECODE( 6, '(3I2)', S ) V 
   WRITE( *, '(3I3)') V 
   ENCODE( 6, '(3I2)', T ) V(3), V(2), V(1) 
   PRINT *, T 
   END

The above program has this output:

98 76 54
547698

The DECODE reads the characters of S as 3 integers, and stores them into V(1), V(2), and V(3).
The ENCODE statement writes the values V(3), V(2), and V(1) into T as characters; T then contains ‘547698’.

ENCODE and DECODE are old Fortran extensions (not sure if they were ever part of an official standard) that have been replaced by internal file reads/writes

Modern Fortran code for this would look like

use iso_fortran_env, only: i4=>INT32
character(LEN=6) :: S="987654"
character(LEN=6) :: T
integer(i4) :: v(3)

read(S, '(3I2)') v ! reads string into integer array
write(*,'(3i3)') v
T=repeat(" ",6) ! make T all blanks first
write(T, '(3i2)') v(3), v(2), v(1) ! writes integer values into string T
print *, T

I would write instead

T= ""

And put an end on the last line.

They were not.

I didn’t know either what encode/decode does. I pasted your query to chatGPT and it seems it did a pretty good job explaining what the code does: Code Explanation: Line-by-Line.

2 Likes

Yes, and ChatGPT-4 translates the code to standard Fortran when asked, giving the same output as the code by @rwmsu

PROGRAM translate
    IMPLICIT NONE
    CHARACTER(len=6) :: s = '987654'
    CHARACTER(len=6) :: t
    INTEGER, DIMENSION(3) :: v

    READ(s,'(3I2)') v
    WRITE(*,'(3I3)') v

    WRITE(t,'(3I2)') v(3), v(2), v(1)
    PRINT *, t
END PROGRAM translate
1 Like

“Yes, and ChatGPT-4 translates the code to standard Fortran when asked, giving the same output as the code by @rwmsu

well that make sense since a lot of people tell me my intelligence is “artificial” :smile:

1 Like

They weren’t standard, but they were a common extension.

F77 replaced that functionality with internal i/o. The other thing that f77 added was a character data type. Before that, characters were encoded into integers (and also real, logical, and double precision types) with either Hollerith constants or with external i/o. Almost all of the code I saw that used encode/decode involved packing and unpacking characters in integer variables.

The posted code would appear to be an anomaly in this respect because it uses character variables (f77 and later) but it does not use internal i/o (also f77). So this was probably an older (before f77) legacy code that was just partially modernized at one time.

Used ENCODE and DECODE, have converted a number of codes to use internal reads and writes that contained it; still know of a few codes that use it because at least with one vendor
it is(was?) far faster than internal reads and writes (no idea if that is/was the case with other compilers; few codes I worked with were dominated enough by their time in ENCODE/DECODE to not convert them to standard syntax).

gfortran(1) does not support it, but ifort still does. Is that what you used?

So ENCODE and DECODE were old hat to me. The surprise was
the “INTEGER V(3)*4”. I have see "INTEGER*4 V(3) many times, but do not recall every seeing that before. Maybe I did and forgot; but pretty sure I never saw it.

Similar to your INTEGER V(3)*4 are the declarations of the arrays X and Y in the following code.

program tst
implicit none
real x(3)*4, y(4)*8    ! x is SP, y is DP
print *,kind(x),kind(y)
end program

The NAG and Silverfrost compilers accept this code, Intel and Gfortran do not.

Looking at Beliavsky’s code:

Re the code that baffles me, it still does, what is the use, or the appliccability. Is some priciple being illustrated?

Where did you find the code in your original post?

One commonly wants to read data from a character variable, for example to get the integers 2022, 6, 20 from the string “2023-06-20”. This can be done with an internal read, as illustrated above.