Changing . to % to access components of derived types

I sometimes come across Fortran code that uses the non-standard . instead of % to access derived type components. Is there a tool that converts . to % for such uses and does not make other changes? There are places in Fortran where the replacement cannot be made, as in .eq., and the tool must not change those.

I asked claude.ai to write a Python script to do it, but you need to avoid replacing . with %
in (both lower and upper case)

  • comparison operators such as .eq.
  • numeric literals such as 3.14
  • logical literals such as .true. and .false.
  • format strings such as f8.2
  • quoted text and comments
  • probably other things I have not thought of

and claude.ai was unable to handle all these cases in a few iterations, given the code I linked upthread as a test case.

In general it is not possible, but in practice the above list should work (you forgot user-defined operators). For example, is a.eq.b equal to a (.eq.) b or (a.eq).b? Due to user-defined operators, I think any a.b.c is ambiguous.

2 Likes

Do you have an editor like vim at disposition? If there are not too many instances to edit, then its command of :%s/\./%/gc could be good enough here. Sed like, the old pattern (obviously the period has to be escaped here) is substituted by the new one regardless if it is the first or nth time on the line (flag g). The editor provides an additional safety net though by requiring your confirmation (flag c) on a one-by-one basis i.e., each time you reply by either short hand of ([y]es, [n]o, [a]ll occurrences, [q]uit, …).

Thanks, but I want an automated solution and have thought of one using gfortran. For the code linked in the original message, gfortran -c logger_mo.f90 gives error messages such as

logger_mo.f90:103:16:

  103 |       call this.write ( file_macro, line_macro, '*** Erorr:', trim(iomsg) )
      |                1
Error: Junk after CALL at (1)
logger_mo.f90:122:16:

  122 |       call this.exec ( __FILE__, __LINE__, 'rm -f '//trim(this.file) )
      |                1
Error: Junk after CALL at (1)

One could write a Python (or Perl etc.) script that reads the error message, checks if position 16 of line 103 in the source file is ., and replaces it with % if it is. As @certik implied, you need the functionality of a compiler to detect places where . should be %.

Hi!

I agree that the solution requires the usage of compiler technology, where the context of the operator “.” is known and those different situations can be distinguished properly.

In the Open Catalog of best practices for Fortran modernization, we have documented a rule related to GNU Fortran extensions that are not standard:

PWR075: Avoid using GNU Fortran extensions

In the situation you describe related to the operator “.”, the gfortran compiler is compliant with the Fortran standard and gfortran raises a compilation error. Is this correct?

So, from your experience, what compilers are not compliant with the Fortran standard by accepting the operator “.” as an alternative to “%”?

The list of compilers I have in mind are GNU, LLVM, Intel classic/oneAPI, Nvidia, Cray and NAG. Perhaps any of these? Or any other Fortran compiler?

Overall, i am trying to understand if it makes sense to document a new rule in the Open Catalog for this use case. Later it might be automated in Codee, even including an AutoFix to help with the refactorization of the source code.

By default Intel Fortran compiles and runs the code

implicit none
type :: t
   real :: x
end type
type(t) :: y
y.x = 2.1
print*,y
end

but when compiling with the -stand:f18 option it says

xdot.f90(6): warning #7334: F2018 component is being referenced as if it were a structure type; this is not standard Fortran 2018.   [Y]
y.x = 2.1
^

so I think it is standard-conforming.

The Intel compilers accept . in lieu of %.

I think it has to do with the fact that DEC compilers had a “structure/record” type extension before derived types were introduced into the language.

EDIT: It seems gfortran also supports the extension if you pass the -fdec-structure flag.

2 Likes

SPAG converts . to % in derived types. I tried replacing all “%” in your example to “.”, and SPAG converted them back. It is aware of the context in these cases, so doesn’t change logical operators etc. Of course, it does make other changes, so doesn’t pass your test.

Also, in this example, SPAG doesn’t know about the CRITICAL statement, and I had to change “PURE ELEMENTAL FUNCTION” to “ELEMENTAL FUNCTION” - I’m not sure why that is.

1 Like

That is correct. The extension originally came from VAX/VMS Fortran, so has often been referred to as “VAX structures”.

1 Like

Some related links:

Even a.eq.b is ambiguous. I was wondering how ifx (and gfortran) resolve the ambiguity, so here is a test:

program main
  implicit none
  type :: u
    logical :: b = .false.
  end type
  type :: t
    type(u) :: eq
  end type

  interface operator(.eq.)
    procedure :: op_eq
  end interface

  type(t) :: a
  logical :: z
  logical :: b
  z = a .eq. b
  print *,'z=',z

contains
  logical function op_eq(x, y) result(result)
    class(t), intent(in) :: x
    logical, intent(in) :: y
    print *,"op_eq called"
    result = .true.
  end
end

Compiled with ifx this prints z= F because a.eq.b is interpreted as a%eq%b. The standard-conforming result is for .eq. to map to a call to op_eq and the main program would print z= T.

Even ifx -stand:f18 does not get the right answer, it just give an incorrect warning:
F2018 component is being referenced as if it were a structure type; this is not standard Fortran 2018.

gfortran -fdec-structure gets the same result as ifx, but at least you know you are enabling a non-standard feature and by default it is standard-conforming.

Here are the results on godbolt: Compiler Explorer

3 Likes

The Intel compiler is the DEC compiler successor. Also the -standard-semantics flag doesn’t change the result.

1 Like

@ashe great example. One idea to disambiguate is to use z = a (.eq.) b in ambiguous cases like this one to mean operator .eq.; this syntax is currently rejected by both ifx and gfortran, so we can use it (it’s not used for anything else already).

The fact that ifx and I am guessing also ifort have this behavior on by default (is it even possible to turn it off?) seems to imply that such collisions are not very common in practice.

1 Like

Is it necessary to introduce a new syntax? Doesn’t z=(a).eq.(b) already do that?

1 Like

It does! This is even better. I tried it in the compiler explorer and all three versions give T now. So when you do z = (a) .eq. (b), it is interpreted as operator .eq.. And when you do a.eq.b, it is interpreted as member access (if . support is enabled in GFortran or Ifx).

From a high level, these examples may be a warning to Flang and LFortran teams to really think about whether or not to support old crusty vendor extensions. Intel Fortran doesn’t have a choice, we have to support these. It would seem, from the outside, that surely the -stand or -standard-semantics SHOULD catch these. The trouble is, this semantic analysis is downstream from the tokenizer and parsing where the confusion forced a choice one way or another.
It’s a good high level discussion that should occur for compilers under development - support old extensions or stay pure? These are a great arguments for staying pure. Counter argument, I think most users would not write anything like the above syntax, realizing it could confuse the compiler. And therefore supporting old vendor extensions may be worth it to help bring onboard old dusty deck (DEC?) applications.

4 Likes

@greenrongreen yes, I agree with you. The added peculiarity here is that I actually like the “.” much more than “%” for member access. Every single new Fortran user asks what % means, and it’s in my opinion an unnecessary obstacle. And yes, one can just live with it, but I think “.” is better. However, currently we have much more higher priority issues to chase. Also given all the technical issues above, I don’t know if it is worth pursuing.

@greenrongreen ,

CC: @devorah

It is a shame better imagination cannot be realized.

So Intel Fortran now has a driver “ifx” with which anyone seeking to stay away from “old crusty vendor extensions” has to append “-standard-semantics -stand -warn:stderrors”. Such appendix is simply impractical to deploy across a global enterprise and otherwise, it’s unenforceable. Practitioners inevitably overlook which lead to costly mistakes. As a customer of Intel, those who seek to rely on the standard (and quest to be “pure”) need something easy and convenient from the vendor.

There are many customers, including the teams I work with, that represent Enterprises who procure >US$25 million worth of Intel processors each year and who have global presence and working om important societal needs globally such as transforming the world energy sector away from carbon-based sources to renewables, etc. (that is on “a higher purpose” that Intel’s own CEO touts on public forums) and for these customers, computing is critical and Fortran can play a pivotal role and who are requesting the vendor Intel to provide an out-of-the-box driver, say “IFS” which is equivalent to ifx with the “-sfandard-semantics -stand -warn:stderrors”

Why are these customers ignored by Intel? Why is Intel so hellbent on primarily serving the needs of those who seek to stick to “old dusty deck (DEC?) applications” but doing little to bring customer delight including with Fortran to new areas?

It makes no business sense whatsoever. Presently many of the customers are moving away from Fortran, and ultimately away from Intel processors. Intel, seriously you’ve a problem. And you can start to address them by focusing on smaller aspects within your sphere of influence, here it is Fortran.

A backward compatible way to define this extension would be to say that a.b.c is a reference to operator(.b.) if .b. is an intrinsic operator or a user-defined one that is in scope. The user can always specify the other meaning with a%b%c. And, of course, not use derived type member names that are the same as operator names.