Format sentence of Fortran

Please suggest me some reading for understanding format in Fortran

Fortran Courses in Fortran Wiki is the place to start online, but formatting I/o is a language within a language, and if you have a more specific question do ask.

1 Like

My reference is chapter 11 “Edit descriptors” of Modern Fortran Explained: Incorporating Fortran 2018

1 Like

Here is another online resource: FORMAT
Mind you: an explanation of the “words” of this little language is not the same as a “grammar” or an “idiom”. As @NormanKirkby indicated, you may be better off to ask about specific problems that you need to solve.

1 Like

Here is a program that illustrates some Fortran formats. The output of a print statement is given in comment lines below it.

program formats
implicit none
real :: x(3) = [4.0,9.0,16.0]
integer :: v(3) = [4,9,16]
print*,x(1) ! * gives list-directed output. It is general and 
            ! can be used for all types, but results will differ by compiler.
! Format strings start and end with parentheses.
! The fw.d format prints a floating point number using width w 
! and with d numbers after the decimal point.
print "(f6.2)",x(1) 
! 4.00
! Due to format reversion, the line below will print each element of x(:)
! on a separate line. See online Dr. Fortran essay "Revert! Revert! The End (of the format) is Nigh!"
print "(f6.2)",x 
!  4.00
!  9.00
! 16.00
! Print two floats on each line
print "(f6.2,f6.2)",x 
!   4.00  9.00
!  16.00
! Use a "repeat edit descriptor" to do the same thing
print "(2f6.2)",x 
!   4.00  9.00
!  16.00
! Use an "infinite repeat count" to print all floats on same line
print "(*(f6.2))",x 
!   4.00  9.00 16.00
! Use minimum field width descriptor f0.d to print in the smallest width possible
! The 3x is used to put 3 spaces between the numbers.
print "(*(3x,f0.2))",x 
!    4.00   9.00   16.00
! Print with comma separators. The : suppresses a comma after the final item
print "(*(f0.2,:,','))",x 
! 4.00,9.00,16.00
! For integers the iw descriptor prints an integer using width w, and i0 uses minimum width.
print "(i6)",v
!      4
!      9
!     16
print "(*(1x,i0))",v
!  4 9 16
! A format such iw.w will print leading zeros to fit the width
print "(*(1x,i4.4))",1,12,123,1234,12345
! 0001 0012 0123 1234 ****
! For character variables there is the 'a' edit descriptor. aw means using width w. 
! Just 'a' uses the width of the character variable.
print "(a4)","boy","girl"
!  boy
! girl
print "(a)","boy","girl"
! boy
! girl
! logical variables are printed as T or F, with the l edit desciptor.
print "(*(l3))",.true.,.false.
!   T  F
! The g (general) edit desciptor can be used to print any type. One form is g0.
print "(*(1x,g0))", x,v,"boy","girl",.true.,.false.
! 4.000000 9.000000 16.00000 4 9 16 boy girl T F
! / starts a new line
print "(*(i0,1x,i0/,a,1x,a))", 3,5,"girl","boy"
! 3 5
! girl boy
! If there is insufficient width to print a number, asterisks will be printed.
print "(f3.1)",4.2,1234567.8
! 4.2
! ***
! There are scientific notation formats such as e and es for floating point
! that can help avoid such overflow.
print "(e15.8)",4.2,1234567.8
!  0.41999998E+01
!  0.12345678E+07
print "(es15.8)",4.2,1234567.8
!  4.19999981E+00
!  1.23456775E+06
! A repeat edit descriptor can be used for a parenthesized list of edit descriptors.
print "(2(1x,2(i2.2,':'),i2.2))",8,59,59,11,59,59
!  08:59:59 11:59:59
end program formats
2 Likes

A good reference I like for Fortran formatting is:
Formatted Input and Output by Dr. C.K. Shene.
Dr. Shene’s slide deck is linked to by Learn — Fortran Programming Language.
[Scroll down to the online courses section, and look for Fortran 90 Tutorial]

Nesting and reuse and repeat are among some of the unique features for Fortran FORMATs partly because Fortran did not initially allow composing a line using non-advancing I/O or internal I/O accept for the long-defunct but once common ENCODE and DECODE statements.

The basic descriptors are not that hard to understand when applied to outputting a single value. I think approaching it that way, and coming to understand how to output a single value first simplifies understanding Fortran formats. Get that down and then experiment with tab descriptors, format nesting, repeats, reuse, internal I/O and non-advancing I/O after you know what all those basic descriptors do to a single value.

. But a syllabus centered around plain text file I/O might include a lot of other topics as well. For example, here is one such:

TOPICS

FORMATTED I/O and other common human-readable forms

o PRINT versus WRITE()
o * versus INPUT_UNIT, OUTPUT_UNIT, and ERROR_UNIT

OPTIONAL: List-directed (* format)
o List-directed output – easy with pitfalls
o common differences – “table length” versus minimum length; line length
o List-directed input – skipping and repeating and other unexpected features
o controlling line length
o A small excursion: The PAD= attribute makes a difference

OPTIONAL: Namelist
o Namelist input
o Namelist output – creating different groups with variables in multiple namelists
o printing a subsection of an array or other subsets of data
o great for user-defined types, debugging, …
o interactive use with a running program (and M_namelist and M_matrix as an alternative)

o writing and reading into (optionally multi-line) character arrays
o using I/O to convert numerics to and from character strings

o basic concepts of advancing, non-advancing, stream
o writing a blank line
o Formatted input and 0 descriptor
o Formatted output and 0 descriptor, g0, f0, e0, …

o all the descriptors
o each according to its type
Data edit descriptors: I, B, O, Z, F, E, EN, ES, D, G, L, and A.
o engineering versus scientific

   Control edit descriptors: T, TL, TR, X, S, SP, SS, BN, BZ, P, :, / 
   o whitespace on input
   o difference in tab descriptors when advancing, non-advancing, and stream
     o buffering and tabbing in the line

   String edit descriptors:  H, ĘźstringĘź, and "string" 
   commas and slashes (/):

o a format is used until the values are exhausted, with an automatic \n added on advancing I/O
o adding linebreaks with / versus new_line(‘a’) and cr-lf versus lf

o repeating a format section
o stopping with colon (:), and how to get that ending string to print

o Number of significant digits versus field lengths

o creating a fmt() function
o creating a write() function

o inquire how many characters a statement will write
o **** and iostat and handling I/O errors
o EOR and EOF

o writing to stderr

o highlights of pertinent OPEN options

o writing a format on the fly
o figuring out how long a write would be
o creating tables with ASCII text
o UTF8
o tabs and other non-printing characters and ADEs (and M_strings)
o printing small arrays (and M_display)
o adding color to output (and M_escape)

o options on OPEN that should be specified, not defaulted

o data does not need to be formatted or sequential – the pros and
cons of binary data and positioning stream I/O and direct-access
files.
o high-level I/O and XML, HDF5,
o CSV, HTML, JSON, TOML, …

o reading lines of unknown length for subsequent parsing
o stream I/O on stdin and stdout

o FORMAT vs character strings as formats

o PDTs

o dusty corners
o non-advancing I/O has a line length and is not streaming I/O
o filenames: non-ANSI, filenames with spaces, case, length, trimmed names
o BOZ and formats and rounding used to keep values
o NaN and Infinity
o box characters
o screen formatting (and M_ncurses)
o ANSI escape sequences, tput, …
o ASA carriage control (and asa2pdf)
o common collisions with cpp(1) variants
o dos2unix and unix2dos – it isn’t just line terminators
o HOLLERITH constants
o VFEs (variable format expressions), $, Q, and / are NOT standard
and how to do the same thing with standard code.
o commas on input

    The comma is an external field separator for formatted input. This
    adds a touch of list-directed input into formatted input.

    The comma terminates the input of a value when encountered in
    a field that is shorter than the number of characters expected
    (for non-character data types).  It can also designate null
    (zero-length) fields.

If none of those topics raise questions you have it all down :smile

I might feed the topics into ChatGPT out of curiosity.

1 Like

Shene’s ‘Formatted Input and Output’ is somewhat out of date. It does not mention w=0 in Fw.d output (standard since F2003) or E, ES, EN, or Gw.d output (standard since F2018). In addition it says that in E, ES, or EN
format output there will always be an E in what is written. But according to the standard the E is omitted if the format has no Ee part and the value to be written needs 3 exponent digits, as in this program:

  real(kind(1d0)):: x = 1/3.d-200
  print "(ES0.15)", x
  end program

Output from ifort or ifx, which IMHO is standard-conforming:

3.333333333333333+199

(I intend to send gfortran and lfortran bug reports because they give different outputs.)

No, that is not conforming. See Interp F18/033. Intel has not picked up on this yet. (NAG hasn’t either.) The interp edits are part of F2023 and a Corrigendum to F2018.

2 Likes

@sblionel is right. Always including E in Dw.d, Ew.d, ESw.d, or ENw.d output if w = 0 is one of the few topics on which “Modern Fortran Explained” misleads. See F2023 Tables 13.1, 13.2, and 13.3. But if w > 0 and the decimal exponent needs three digits then the E must still be omitted from the output, as already in F66 7.2.3.6.2.1 for Ew.d.

I would not say “misleads” - as the interp says, F2018 and earlier did not reflect the intent of w=0, and also failed to establish an interpretation when Ee is omitted, and the exponent is more than three digits. Compare to the same tables in F2018.

What I find interesting is that nobody raised this issue until I saw a complaint about it in the Intel forum and started poking at it. (I spent many years of my career working on the Fortran I/O system, so I take such things personally!)

In F2008 Tables 10.1, 10.2 and 10.3 suggest that E, D, EN and ES formats
must not omit Ee if |exp| > 999. Some compilers already offered real types needing four digits. So could part of the F2018 interp have been an interp to F2008 ?

Once a new standard has been published, interps for previous editions are no longer produced. It is often the case that an interp corrects wording that also appeared in earlier standards, but we don’t care about that.

I think your reply belongs in the other thread: Omission in the Fortran 2023 Standard? - #11 by ClivePage.

Whoops - yes. Thanks.