Why are parens required around format strings?

Have had different compilers treat T and X as actually generating spaces and as just preparing to print the next value there; particularly an issue when using non-advancing I/O. There were just some recent changes to ifx and gfortran in ththee relatively recen but past addressing some of the ambiguities there. Most compilers probably do not add a space because of the 1X but because that has been (is?) a point of different interpretations I think adding the colon is a good idea.In particular if WRITE also had a default format it would be important to be clear about that as with WRITE you can do non-advancing and stream I/O and so on.
I have only thought about this as applying to PRINT but that is still a good point.

And sometimes the colon is critical to a format working as intended. The “bracket” format would not work at all without it.

program demo_trim
implicit none
character(len=:), allocatable :: strs(:)
character(len=*),parameter :: brackets='( *("[",g0,"]":,1x) )'
integer :: i

   ! array elements are all the same length
   strs=[character(len=10) :: "Z"," a b c","ABC",""]

   write(*,*)'untrimmed:'
   ! everything prints as ten characters; nice for neat columns
   print brackets, (strs(i), i=1,size(strs))
   print brackets, (strs(i), i=size(strs),1,-1)
   write(*,*)'trimmed:'
   ! everything prints trimmed
   print brackets, (trim(strs(i)), i=1,size(strs))
   print brackets, (trim(strs(i)), i=size(strs),1,-1)
   print *
   print brackets, 10, sqrt(11.0), (10,20)

end program demo_trim
 untrimmed:
[Z         ] [ a b c    ] [ABC       ] [          ]
[          ] [ABC       ] [ a b c    ] [Z         ]
 trimmed:
[Z] [ a b c] [ABC] []
[] [ABC] [ a b c] [Z]

[10] [3.31662488] [10.0000000] [20.0000000]

One caveat about the “ALL” format is that it does not print complex numbers like list-directed or NAMELIST output but just as two float values.

Another frustrating one is that list-directed output and NAMELIST can come really close to generating CSV files. There should be an option when writing NAMELIST groups or on the PRINT statement to generate CSV files.

program demo_csv
use iso_fortran_env, only : stdout=>OUTPUT_UNIT
implicit none
character(len=*),parameter :: comma='( *(g0:,",") )'
character(len=:),allocatable :: str1, str2
   ! generating CSV output assuming no quotes in strings
   str1="  some string "
   str2='another'
   print comma, [10,20,30],40,50,60,'"'//str1//'"',sqrt(10.0),'"'//str2//'"',sqrt(33.0)
end program demo_csv
10,20,30,40,50,60,"  some string ",3.16227770,"another",5.74456263

For somple cases you can use something like the example which incorporates your colon suggestion.

I have the same wishlist, so currently I use a CPP macro and write print statements (w/o formats) like put foo, baa, arr(:) etc, although I need to be careful about complex literals, IIRC. (BTW, I learned this format string from comp.lang.fortran, so thanks very much!) It may also be possible to add enclosing parentheses for a format argument, but I haven’t tried yet…

!! my convenience macros (included via an include file)
#define put          write(6,'(*(g0,2x))')   /* to remove the leading space */
#define putf(x)      write(6,x)
...

I also define a “macro” for implicit none, assert, etc like

#define ___          implicit none
...
#define assert(x)  ...
...

so I never explicitly write implicit none in my codes. (I initially chose explicit as a macro name, but I settled down to the above one later.) But one downside of this kind of macro is that syntax highlighting etc does not work for redefined keywords (unless related configuration files are modified). In my case I modify the Emacs init file to highlight such macro names (as well as % etc).

BTW, when I do coding in python etc for some time and go back to Fortran, I once wrote print foo, baa, arr(:), which resulted in an error. But at that time I was not able to understand why (for 10 seconds?). Then I noticed that I missed *, after print… Similarly, I once forgot to write the enclosing parentheses in a format string (...), and … (similar pattern). But a more serious error was that, I once wrote continue instead of cycle in a loop, which resulted in a silent bug… (but fortunately it was found pretty soon).

I guess this is obvious, but when a compiler sees

read a, b, c
print a, b, c

how would it decide if a is the format field or the first element of the list? I think that is why the format field (which can be a character expression, a format statement label, or a *) is required in these two cases.

Regarding what is the default format for list-directed write, another possibility is to allow such things as the leading space, maximum line length, default advance=, and the default formats for the various types to be modified, e.g. with an open statement. The open statement already allows a connection to be modified for an existing open file, so this approach would be consistent with that precedence.

I think print(a, b, c) might work. This is really quite simple to solve: we just prototype in a compiler, and we have to ensure all tests pass, to not break backwards compatibility.

Can you explain how namelist is involved here? I only know of namelist output that creates a list of name = value(s) pairs, one per line.

Just some food for thought:

  • if trying to prototype, then consider two new statements to the language, READIN and PRINTOUT.
  • These are effectively READ and PRINT but with a single, defined format in a fashion similar to current list-directed option that requires *,
  • the goal being to avoid the parenthesis when not needed!!
readin a, b, c
printout a, b, c

In fixed form source, these statements would be equivalent to

read ina, b, c
print outa, b, c

The current fortran source code conventions are that anything that can be done with one source from can be done with the other, so that would eliminate these cases that are only distinguished with spaces.

Also, the current standard *, sequence consists of only two characters, so replacing that with parentheses or with longer keywords doesn’t really reduce the number of characters that the programmer must type.

But if fixed-form has been declared obsolescent, is it worth taking into consideration in the design of new features? The situations reminds me of the legend that standard-gauge railways are based on roman chariots.

2 Likes

NAMELIST is only indirectly involved. It is very free as to the output, much like list-directed I/O as far as line breaks and use of whitespace but notice that if DELIM=‘quote’ on the output unit that the output is essentially CSV if you remove the KEYWORD= strings and header and footer and place it on one line. So it would be virtually trivial to allow for an option to write NAMELIST groups in CSV format. NAMELIST already handles user-defined types as well. The way it prints COMPLEX values is not probably conformant to most CSV variants but that is about it. People are often using FORMATs to format data as XML, JSON, TOML, YAML, … many of which seem like natural extensions to NAMELIST. CSV origins have strong ties to early Fortran so it is a little ironic it is not totally trivial to generate with Fortran. NAMELIST groups seem like a natural for outputting “standard” formats, alleviating the burden of doing that from the user. But a lot of those “standards” are loosely defined, which is problematic.

2 Likes

I think “obsolescent” means that a better way of doing something exists, but it is still part of the language that still must be supported, right? If so, then I guess it is a question of when the new feature is added compared to when the old feature is eventually deleted from the language. If the new feature is targeted for the next language revision (say in three years), and the old feature is expected to be supported for the next decade, then yes it is worth taking their compatibility into consideration.

That is an interesting article. One important point is that sometimes the exact specifications are not so important, but rather the standardization process itself is paramount. From the above article, the 19th century American Confederacy had multiple train gauges, and “This lack of standardization was, as historian James McPherson pointed out, one of the many reasons the Union was able to finally vanquish the Confederacy militarily […]” That is, if the Union’s standard gauge had been an inch wider, or an inch narrower, it would not have made a significant difference, the critical thing was that all of the Union’s locomotives and train cars could go anywhere they needed to go, unlike the Confederate locomotives and train cars.

This principal also applies to programming language standardization. Sometimes the details of the syntax are not the critical thing, it is the fact that every compiler and every source code conforms to the standard that is the important feature.

3 Likes

Let’s get real.

print *, “hello”

Folks, all y’all need to just leave it alone. Changes in syntax are not ‘easy’. It takes effort and time from people like me, most of us unpaid, doing it for the good of the order, to change things. It’s not trivial. Please stop enhancing what is truly an elegant and powerful programming language.

5 Likes

Agree! Read and write statements in Fortran work well, are pretty robust, and straightforward. They meet the requirements of a scientific programming language, and then some.

Let’s not fix what is already working, and pretty well. I don’t need my IO statement to make me coffee!

I do think I should be able to write

print x, y

instead of

print*,x, y

but a tool external to a Fortran compiler can supply the extra syntax. Often my codes don’t compile because I forget a contains statement or put implicit none before use statements, and a tool could fix those errors too. I think coding assistants powered by LLMs will be created that learn from a coder’s common errors and fix mistakes on the fly.

Fortran can be verbose – my modules start with boilerplate such as

module m
use kind_mod, only: dp
implicit none
private
public :: foo, bar
contains

Maybe a text editor could configured to hide the boilerplate or streamlined version of the source file could be created for viewing.

Are the extra *, really that problematic? C languages require a ; at the end of EVERY line, and Python imposes strict indentation.

That said I agree with you that such extensions are best left to external tools. As for verbosity, all languages suffer from it to varying degrees. It is a necessary evil for any language designed for the Neumann computers we currently work with. Fortran is much less verbose than C++ when designing classes, for example.

As discussed above, how could a fortran compiler, or an external tool, know whether you intend x to be the format or part of the output list? It seems to me that the proposed syntax is ambiguous.

I know of two features that are missing, and with the current capabilities, are not trivial to replicate. These are for floating point values. One feature is to output the maximum number of significant figures within a specified field width. The other is given the number of significant figures, output the value in the minimum field width. In both cases, this means that optional signs, leading zeros, and perhaps the entire exponent field are eliminated or minimized. The first format would be useful for printing aligned columns of values, while the second would be useful for writing numbers within text sentences.

Yes, “Let’s get real”. Ultimately this all boils down to dogma which is best questioned always and challenged vehemently. Otherwise, there is no progress. People can go back to not counting at all, or counting with fingers, or using abacus, or slide rule, or computing with assembly or whatever. Why Fortran at all?

So yes, to “get real” here will be for those who should know or seek to do better (e.g., @Beliavsky likes the post but immediately follows up with “I do think I should be able to write print x, y” similar to the statement upthread by @certik with " print("Hello") would be awesome") to entirely ignore such tripe and soldier on.

Because the practitioners of Fortran need to understand the practice cannot remain rooted in the past and be permanently held hostage to earlier decisions, that’ll be asinine.

@certik wrote " print("Hello") would be awesome, if it is possible"

Note the entire thing around “if it is possible” hinges around one phrase in the standard in section 6.3.3 Fixed source form, “Except in a character context, blanks are insignificant and may be used freely throughout the program”

Something’s gotta give at some point with things like this, why not now? It is not as if the language standard committee has a perfect “batting record” with not breaking programs, enough things have been broken to further challenge dogma which is entirely a biased assessment of what is meant by “backward compatibility” - things that I or my “frends” like or keep on using like luddites shall not be “broken” but other stuff can be - yeah, get real!!

I have never contributed source code to a compiler, so if there is cosmetic change to the language that an implementer says would take considerable work to implement, I will defer to them.

Why not start today? It’s not hard. I’ll help you (and anyone else in this thread!). :slight_smile:

I agree with @JerryD, @zbinkz and others that print("Hello") is low in the priority list of what we need to work on right now and that it might not be worth (or even possible) to fix. I don’t agree that print *, "Hello" is elegant though. I agree with @FortranFan’s vision to improve Fortran. I teach Fortran to new people, and good natural syntax is important, I believe we should not settle to teach “just put implicit none there and get used to it”, that is not elegant in my view. I agree with @JerryD that our goal should be an elegant language. It’s quite close.

3 Likes

Isn’t this essentially G0.d?