Slash separator

I was surprised when this program did not make ios nonzero when reading / and expecting an integer but both the compilers I used were quite right: the slash (/) is a valid separator in list-directed input, but I had never used it as such. My question: why does Fortran allow it? I note that it was already a possibility in f77.

  implicit none
  integer i,ios
  do
     print *, 'Enter an integer'
     read(*,*,iostat=ios) i
     print *,'i=',i,' ios=',ios
     if(ios/=0) stop 'i was not an integer'
  end do
end program
1 Like

A fortran-lang problem: the original line 4 of my program said print *,‘Enter an integer’ but the asterisk was missing from what appeared in fortran-lang even though when I tried to edit the posting the asterisk was there! Apologies if you were confused. It is apparently possible to edit one’s contributions after they have been sent but I do not know how to.

In markdown an asterisk is a special character and so must be escaped with a backslash in front of it. You do not have to do that and get syntax highlighting if you enter your fortran code between the lines “```fortran” and “```”. For example:

print *,"hello world!"

A slash is not a separator, it ends input without an error, so you can enter partial input records. A [return] acts just like a space, so if you had the following program and only wanted to change the value of “i”, you could enter

100 /

and without getting an I/O error, “j” would remain unchanged and I would be entered.
Otherwise, it is going to keep reading till you enter values for “i” and “j”. It also allows for null values, and the form r*c where “r” is a repeater, so if you had ten values you wanted to set to zero you could enter “10*0”; for example. These used to be features more commonly used, but I find a lot of people are unaware of them anymore.

program testit
implicit none ,j,ios
i=1111
j=2222
do
   print *, "Enter two integers   "
   read(*,*,iostat=ios) i,j
   if(ios.ne.0)then
      print *,"os="  ,ios
   else
      print *,"i="  ,i, "j=",j
   endif
   if(ios/=0) stop    "i was not an integer"
end do
end program testit

You can try a few input lines like:

,4444
66666/
1*,8888
2*9999

If you know what those are going to do you are well on your way to knowing about list-directed input. Other unexpected things (other than null values, repeaters, and terminators for partial reads …) is that strings do not need quoted if just alphanumeric strings. Some people put comments after the input terminator ("/"). I do not remember any more, but “/” was probably chosen because it cannot appear in a numeric value and is unusual in strings; but most importantly it was on all keyboards (hard to believe, but a lot of characters were not standardized and EBCDIC was very common, so you did not want to depend on characters like @, #, ~, |, … as they were often not available, although things like 1/2 often were.

I rarely see these things mentioned, like to read only the 11th value in an input list you can enter “10*,7777 /”; but they are described in the Fortran Standard. I still run across some old program input files that I have to “interpret” for people; but I rarely see these features used anymore; partly probably because they are rarely documented.

Note even in your simple program that only reads one value “/” can be useful. You can basically get a prompt to read “i” and decide you do not want to change the value and just enter “/”.

2 Likes

A more realistic example. Suppose you have a program that prompts you for values
to translate, scale, and/or rotate an object.

program testit
implicit none 
real :: x=0.0,y=0.0,z=0.0, sx=1.0,sy=1.0,sz=1.0, rx=0.0,ry=0.0,rz=0.0
integer :: ios
character(len=256) :: msg
do
   print *, "Enter transformation (translate x,y,z;scale x y z;rotate x y z"
   print *, 'translate .........',x,y,z
   print *, 'scale .............',sx,sy,sz
   print *, 'rotate (degrees)...',rx,ry,rz
   read(*,*,iostat=ios,iomsg=msg) x,y,z,sx,sy,sz,rx,ry,rz
   if(ios.ne.0)then
      print *,"<ERROR>",trim(msg)
   endif

end do
end program testit

If I just wanted to rotate 45 degrees around the Z axis I could enter

3*,3*,,,45

or scale everything by two

,,,3*2/
2 Likes

A slash is called a separator in the F2018 standard 13.10.2 note 1. Elsewhere in the standard it is called a value separator even though as urbanjost said it does not separate values. I shall be interested to see whether the next version of the standard fixes this anomaly.

That is odd wording, but no one ever accused the Standard of being in english.
It does have a note about it, in section 10.10, sentence 3:


 3 A value separator is

       a comma optionally preceded by one or more contiguous blanks and optionally followed by one or more
        contiguous blanks, unless the decimal edit mode is COMMA, in which case a semicolon is used in place of
        the comma,
       a slash optionally preceded by one or more contiguous blanks and optionally followed by one or more
        contiguous blanks, or
       one or more contiguous blanks between two nonblank values or following the last nonblank value, where a
        nonblank value is a constant, an r *c form, or an r * form.

         NOTE 10.27
         Although a slash encountered in an input record is referred to as a separator, it actually causes termination
         of list-directed and namelist input statements; it does not actually separate two values.

          NOTE 10.28
          If no list items are specified in a list-directed input/output statement, one input record is skipped or one
          empty output record is written.

But list-directed input is more than just free-format input; which is generally how it is treated in most descriptions.

As an aside, someone was gone unexpectedly and someone else did not know what to make of a bunch of files that were just commas and asterisks and the words Texas and Florida scattered around in it. Should they keep them? Took a while to realize it was an input file for a little throw-away program that read an array of logical values. It was just lines like “30*,Texas,Florida,10*Florida,3*,Texas.”. Always will wonder why he did that; it was probably some private joke; but they were legitimate input files.

In list-directed input, “Texas” is a legitimate representation of “.true.”, and “Florida” works for “.false.”.

I enjoyed @urbanjost’s comments on list-directed input, and wrote a little test program for amusement:

program LDInput
implicit none
integer, parameter :: NStates = 4
character(13) State(NStates)
integer i
character(37) :: Line = 'Florida,Texas,Tennessee,Massachusetts'
read(Line,*)State  ! list-directed read, not allowed
print 10,(i,state(i),i=1,NStates)
10 format(i2,2x,A13)
end program

The standard says (F2018, 12.4) Reading and writing records shall be accomplished only by sequential access formatted data transfer statements. The program violates this, but none of the compilers that I tried complained about that.
P.S. I looked up the standards. The last sentence was true for F77, which explicitly prohibited list-directed input. In F95, that rule was relaxed, now prohibiting namelist formatting. In F2018, that restriction is also removed. Thus, when I complained about compilers not complaining, I had F77 rules in mind. And, as @Harper points out below, “formatted” includes “list-directed” and “namelist” as sub-categories…

1 Like

Well, along those lines; and with apologies to Floridians because they were the only choice, I know some Texans that would agree

program testit
implicit none 
character(len=30) :: states(3)=[character(len=30) :: "Texas","Florida","Massachusetts"]
logical :: state
integer :: ios, i
do i=1,size(states)
   read(states(i),*,iostat=ios) state
   if(ios.ne.0)then
      print *,"no one knows what ",trim(states(i))," is"
   else
      print *,trim(states(i))," is",state
   endif
end do
end program testit

because in list-directed input a word beginning with “T” is true, and with “F” is false :wink:

I think mecej4 has found a bug in the standard, not in some compilers. That is because F2018 12.3.3.2 defines sequential access only for external files, where it explains the order of records. An internal file can also have more than one record, though mecej4’s example does not. List-directed reading is formatted: 12.6.4.4 begins “1 If the input/output control list contains * as a format, list-directed formatting is established.”

It looks like “/” got clumped in as a “value separator” because it was awkward to keep saying something like “a slash not part of a string constant”; as in 9.6.5 is also says “/” terminates input; and a format used to be required for internal reads and list-directed I/O was allowed later; and the wording got a little awkward. Just a guess. Could stand a little cleanup. It is there, but scattered around in pieces. Had not looked at the description of list-directed I/O in a while. It mirrors NAMELIST I/O in many ways; perhaps it should be re-written as a combined section on NAMELIST and list-directed I/O.