Question about the use of common blocks

I am trying to consolidate my old code and note that in one of the included files, xvar.h, I have this common declaration…

common/ahycopacity/rhyr(23),thyr(28),auxchyop(23,28)

In my program file within one subroutine, I then have this line…

common /ahycopacity/ Rhoref(23), Tref(28), rkapparef(23,28)

This particular subroutine does not include the xvar.h file.

Would the compiler see these as the same thing or treat both as separate, so creating two common blocks in memory with the same name?

It will create a single common block, as only the name is distinctive. That is why you need to use include files, to keep the declarations of the variables in the common block in sync. It is quite legal to do:

COMMON /A/ R(1000)

in one program unit and

COMMON /A/ X(10), Y(20), i(200)

in another program unit (even if they reside in the same source file). Note that I rely on the implicit typing of old in these two fragments :slight_smile:

Sorry, would you mind expanding on this a little for me?

Well, in the old days, before the advent of Fortran 90, it was quite usual to rely on the first letter of a variable’s name to identify its type: A-H and O-Z for default reals, I-N for integers. This is still in effect, but everyone (for a suitable value of “every”) agrees that you should use “IMPLICIT NONE” to avoid such implicit typing.
So the first version of the common block has one REAL array (R), the second has two shorter REAL arrays (X, Y) and a short INTEGER array (I)

1 Like

@garynewport , you may want to review the Fortran standard for storage association that comes into play with COMMON and/or references such as Modern Fortran Explained. This matter can be rather tricky and there is only so much you can “learn” from online forums like this.

And guess what my first include file has as it’s first line!?

IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N)

:laughing:

This is one of the things I am slowly (very slowly) addressing.

Thank you.

1 Like

Currently I am keeping the code as-is to a large extent but will be migrating it across to F90, when I am happy I can do so without breaking too much.

I now have 1 of my 3 books, and my browser has so many reference tabs open. :slight_smile:

I came on here really for clarity of understanding; beginning to secure the understanding but too easy to run down a rabbithole of learning if I am not careful. :laughing:

If you could put the entire codebase somewhere, then people will be able to help you without guessing which important bits you have left out.

1 Like

There are a few reasons for not doing so.
Firstly, I’m not sure I am allowed to. The code originates from another person and I have their permission to work on it but to share it wider…?
Equally, this is part of my PhD research, so I truly need to get my head around the whole thing. Having people solve parts ‘for me’ wouldn’t actually help me - it would simply give me working code.
Finally, I prefer to work through problems; it’s fun. I really appreciate the titbits and specific detail that this forum has provided me; it’s like a safety net where I know I can now come and ask when I find myself lost. :slight_smile:

Is it really legal? My understanding is that a named common block must have the same storage size in all units that are declaring it. Your example, with old implicit typing rules is definitely not conforming to that rule (1000 vs. 230 numerical storage units)

Yes, named common blocks must have the same number of storage units. Blank common does not have to.

Hm, I was not aware of that - but the compiler has no means to check that if you have the various pieces of code in separate files that are compiled separately.
And to get around this limitation, we can always use EQUIVALENCE, right?

My apologies if I have missed it, but I haven’t read the explaination of the COMMON alignment problem.

COMMON has been an essential component of “old FORTRAN”.
It has aquired a bad reputation, which it does not fully deserve.

Modern compilers, such as iFort or gFortran have made using COMMON a bit tricky for the inexperienced, by spacing variables of mixed byte-lengths to optimise performance.
The use of “IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N)” introduces this problem, by typically making reals as 8-byte and integers as 4-byte.

For example, from old FORTRAN, if we have in one routine:

IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N)
common /aaaa/ a,b,k,c, kk

and in another routine:

IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N)
common /aaaa/ idum(7), kk
or
common /aaaa/ dum(3),idum, kk

idum(7) is the equivalent word length for “a,b,k,c” and this would have worked with most old FORTRAN compilers. (idum(131) can be a familiar usage in old COMMON code!)
But with modern iFort or gFortran, the location of kk could be different in the two common.
This is due to the modern compilers introducing a 4-byte filler between K and C for the first example, so that C is aligned on an 8-byte spacing.
In the second example the compiler would not be aware of the included filler.

This is one of the reasons for all COMMON being defined once in a single INCLUDE file, with explicit typing of all variables.
(The other is multiple definitions of the same common in a large code is a maintenance nightmare. modules overcome this with their single definition structure)

@garynewport stated that IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N) is in the first include file, but if this include file is not in all routines, this modified default would not be applied in some routines and other obscure errors would occur. IMPLICIT NONE is a better solution here.

1 Like

I checked that with gfortran-10 and ifort 2021.3.0. Apparently both compilers are aware of the problem. The test code is:

subroutine sub
  IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N)
  common /aaaa/ idum(7), kk
  idum = (/1,2,3,4,5,6,7/)
  kk = 8
  print *, idum
end subroutine sub

program common_test
  IMPLICIT DOUBLE PRECISION (A-H,O-Z), INTEGER(I-N)
  common /aaaa/ a,b,k,c, kk
  call sub
  print *, a,b,k,c,kk
end program common_test

The output from compilers is:

So, gfortran (without the -fno-align-commons option) does align the double but warns about the two declarations resulting in different size of the common (IMHO, it should be an error, but is not, even with -std=f2018 option, still warning)
Intel ifort apparently conforms to the standard requirements by avoiding the alignment. For an architecture which enforces alignment this would be impossible but well, Intel is not for other architectures. And gfortran warns the user.

Not sure I agree with “proper alignment”.
Isn’t this a recent trend with some processor architecture.
Can’t default integers or reals be addressed in memory ?

COMMON deserves its reputation, it has been error-prone, there has too much variance in compiler implementations accompanied by non-standard extensions to complicate matters, and many a coder (often a scientist or engineer whose focus is strongly on domain expertise and less on coding) and programs have suffered the consequences.

The standard committee for Fortran over the years has recognized this and cared enough to acknowledge the fact: Section B.3.11 of the standard (c.f. 18-007r1 document) itself states, “Common blocks are error-prone and have largely been superseded by modules. … Whilst use of … (COMMON) statements was invaluable prior to Fortran 90 they are now redundant and can inhibit performance.”

This concept that COMMON is error-prone and should not be used is very simple logic.
Between 1970 and 1990, COMMON was the main way to manage global data.
To claim it should not be used as it is named “error-prone” is madness.
What will we have next ? Using the wrong variable name is error-prone. Should we remove variables from modern Fortran ?
Perhaps the claim of “error-prone” needs to be better understood. It is applied to many now unfashionable coding styles with little reference to what causes errors in developing or using Fortran codes. Typically it is error-prone because I like something different, looks to be most of the proof. Not much rigour in these proofs ?

If you look at what was achieved in the 70’s and 80’s, these were significant years for Fortran and there are a few who want to redefine what was a successful language, with little proof.
What would also be madness is suggesting to change old codes that work by attempting to remove COMMON. A few contributors should start giving better advice, especially to those maintaining old codes.

2 Likes

Starting with Fortran 90, the language took a path of “safety” that began with type, kind, and rank (TKR) considerations. If those wishing to employ Fortran now cannot pay full heed to TKR, then there is little scope for further discourse.

As I tried to mention briefly upthread but which has been explained in quite a few literature source that have been authored since Fortran 90, the COMMON facility in FORTRAN with its semantics based primarily on storage association and hardly any numbered constraints leave much to be desired in terms of TKR safety. And given the needs of compatibility with FORTRAN 77 and earlier revisions, there is not much that could have been changed.

The use of COMMON allowed code such as the following where TKR considerations can be circumvented in any number of ways:

! A subprogram with implicit interface making use of "global" data named 'dat'
subroutine sub1()
   implicit double precision(a-h,o-z), integer(i-n)
   common / dat / x, y, i, j, z
   ! Instructions employing x, y, i, and z
   x = 1.0d0 ; y = 2.0d0 ; i = 3 ; j = 4; z = 4.0d0
end subroutine 
! Another subprogram with implicit interface making use of "global" data
! named 'dat' differently
subroutine sub2()
   dimension a(4), b(3)
   common / dat / a, i, b
   ! Instructions employing b n, b
   a = 0.0
   i = 42
   b = 1.0
end subroutine 
! A main driver statically allocating memory for "global" data using integers
   integer m(8)
   common / dat / m
   m = 0
   call sub1()
   print *, "main: following sub1, m = ", m, "; expected m(5) = 3"
   call sub2()
   print *, "main:: following sub2, m = ", m, "; expected m(5) = 42"
end

C:\Temp>gfortran -c sub1.f90

C:\Temp>gfortran -c sub2.f90

C:\Temp>gfortran -c f.f90

C:\Temp>gfortran f.o sub1.o sub2.o -o f.exe

C:\Temp>f.exe
main: following sub1, m = 0 1072693248 0 1073741824 3 4 0 1074790400 ; expected m(5) = 3
main:: following sub2, m = 0 0 0 0 42 1065353216 1065353216 1065353216 ; expected m(5) = 42

C:\Temp>

Given what’s possible with Fortran 2018, the above approach I would argue is equivalent to using a chainsaw without any blade guards.

Many a scientist and engineer has had problems with working with such code even though such programs were (and in some domains, are still) prevalent:

  • they would clobber “global” data by working with inconsistent or wrong types,
  • cause misalignment,
  • have programs that lead to inconsistent or inaccurate results depending on program input data, and so forth.

This is one example of what I mean by error-prone that I came to know of whilst refactoring legacy code. Others can provide much better explanation and details than this, for my experience with COMMON is read-only.

As readers can see with the example here, a programmer can continue using COMMON if they so wish. But there are safer alternatives that can also yield portable and performant code. That’s what readers should preferably consider in their codes.

1 Like

I’m not sure what this example was intended to show. The value of m(5) which you get is exactly same as expected. It is the only object in the three differently declared contents of common/dat/ which has the same type, obviously required if the object is meant to exchange information between program units (well, with natural exception of a complex associated with two reals). If one wants to use other members of m, it is plain wrong and the common itself has nothing to do with that, it is a programmer’s error. Common blocks are allowed to have different structure and the standard allows to inter-associate default integer, default real, default logical, double precision real and complex objects. It is up to the programmer to use them correctly. In the prehistoric times when the system memory size was measured in kB, not GB, common blocks could serve as a way to save memory by providing storage used independently in more than one program unit but not enlarging the overall memory requirements. Surely, for that purpose the best was the unnamed common as it had no equal size requirement.

You do not need any common block to circumvent TKR, it is enough to use a subprogram with implicit interface and send wrongly typed arguments to it, as in:

program main
  integer :: i,j,k
  call sub(i,j,k)
  print *,i,j,k
end program main
!
subroutine sub(x,y,z)
  real :: x,y,z
  x = 1.0
  y = 2.0
  z = 3.0
end subroutine sub

put it in separate source files to prevent any inter-unit checks, compile and see the rubbish you get.
BTW, you also mention implicit interface in the comments in your example but I think it is irrelevant there. The bad common blocks would be the same mess with the explicit interfaces (which, AFAIU, for a subroutine with no arguments, do not provide any additional info).

That said, I guess no one tries to prove that common blocks should be used in new code instead of modules. Just let’s not make them the scapegoats for all users’ errors.

In the same sense that the missing blade guard itself has nothing to do with it, it is an operator error to remove one’s fingers. The newer features help the programmer to avoid making these kinds of mistakes.