Question about the use of common blocks

I fully agree. But in the time common blocks were actively used, there was no such blade guard except for using include directives (also non-standard) allowing to keep the block definitions identical in all program units. Thus I think that calling them error-prone is somewhat misleading, especially to younger programmers, as it suggests that the old coots were stupidly using something error-prone instead of something non-error-prone, when the latter was actually not available

2 Likes

What term other than error-prone should be used to communicate to new Fortran programmers that they should not write new code with COMMON, even if they see it in codes they inherit? As you say, the use of an archaic language feature in the past was not a sign of bad judgement if the alternative feature preferred now was not available at the time.

There are fast, well-tested FORTRAN 77 codes out there. I don’t think people are advocating discarding them and writing new codes from scratch. Sometimes the updating will just be to convert them to free source form using a tool and to add interfaces or put code in modules. Or even leave them untouched and write modern Fortran wrappers.

2 Likes

In the old days of mainframe Fortran, COMMON had two main purposes. On these machines, memory was precious, and had to be used sparingly. For instance, the CDC 7600, a $ 5+ million supercomputer of the early 1970s, had 64 k of 60-bit words. These machines did not have stacks, and even local arrays in subprograms used up memory for the duration of the program. Therefore, Fortran programmers declared common blocks in the main program, rather than in subroutines, and these blocks were exposed in the subprograms that needed space for arrays.

One usage of common blocks (or sections of common blocks) was as scratch space. The main program did not read or write any of the variables in the scratch space. Thus, the same scratch space block could be given to different subprograms one after the other. As long as the block was big enough, the types of the variables to be put into it did not matter. Such usage of COMMON is relatively safe.

The second mode of usage of common blocks was as an alternative to argument lists of subprograms, or as an extension of those lists. It is here that lots of errors can occur. Types and sizes must be correctly matched. Just as with argument lists, the order of variables in the common block must be correct, since matching is done by offset from the block beginning. We think in terms of variable names, but in the compiled code it is only the address (relative to the start of the common block) that matters.

Most of the time, moreover, the order of the variables in the declaration has absolutely no meaning or relevance to the usage of the variables in the executable statements. Nevertheless, if a single integer, say, is added in the middle of a common block in one subprogram, all other instances of the same block throughout the program sources have to be changed (here is where putting common block declarations in include files can provide relief). When the contents of a common block variable are used in more than one subprogram, the types must match since, as we have seen earlier in this thread, the integer 123 and the real number 123.0 may have entirely different bit representations (they did not on the CDC).

Thus, it is in the second mode of usage of common blocks, that is, as extensions to argument lists (or as global variables, if you prefer that term) that lots of errors can be made (and are made, in many widely used F77 codes), especially when attempting to modernize or extend such old codes.

[Added on 30 October: After some searching, I found this 2004 article by Tim Hopkins and Les Hatton on using common blocks for work arrays.]

Just because there are other ways there can be program issues does not change the fact COMMON too can cause problems.

In addition, there is history of problems with legacy code, a considerable amount with the teams I have worked with, where it indeed proved difficult and error-prone for many a domain-expert - scientist/engineer - to work with COMMON blocks (and an accompanying feature BLOCK DATA). The issues were compounded by the fact there were significant compiler differences (extensions?) in terms of the handling of COMMON leading to major constraints with portability.

Indeed. I was surprised on one occasion when I had a block data subprogram in a file by itself, and did not link the corresponding OBJ file with the rest of the OBJ files from the other source files (error in makefile). Later, I learned a trick (Les Hatton was mentioned as the creator) to avoid this error: give a name to the block data, say, “BLOCK DATA BLK”, and add “EXTERNAL BLK” in the main program. With this change, a linker error will occur if the block data OBJ file is not included.

1 Like

This is the third application of EXTERNAL, at least in F77, the first two being a declaration of an subprogram to be passed as an argument and a redeclaration of an intrinsic function to be user-written. I agree that it might have been least known.

I think you mention this for the second time already. Could you give some more details/examples? I have never encountered any such problems. And I can hardly imagine any, unless the types of the corresponding objects are messed up.

This is going by memory of what I read whilst working on refactoring of industrial codes (thus the Enterprise held all the copyright) to which I had time-limited access, so please excuse me if I don’t get all the details right. If there were a genuine need, I could loop back and try to fetch details but not sure if that’ll be necessary for the discussion here:

  • one compiler (DEC/VAX or IBM?) would allow initialization of variables using a DATA statement in the subroutine it was declared but another (Microsoft Fortran perhaps?) would only permit that in a BLOCK DATA subprogram.
  • one or more compilers (Microsoft?) would allow variables of CHARACTER type to be present along with INTEGER in a COMMON block but another (IBM?) would require if a CHARACTER variable was present, all the block elements had to be the same type. If I recall correctly, the ANSI FORTRAN standard had close to but slightly different requirements than the latter about CHARACTER type in such a block that was enough to cause problems with one team I know,
  • padding and alignment could be controlled via directives in some cases but there was no such thing with some other compilers,

There were other issues too. Bottom-line: the powers-that-be and the senior technical leaders in many of the teams I worked with had concluded COMMON blocks were problematic and if working with Fortran meant having to use COMMONs and a bunch of other such aspects, then the codes had to migrate away to newer, safer, flexible, convenient, even performant, and productive alternatives.

Thanks a lot for the examples. I truly understand the possible problems that may arise from bad use of common blocks. Still, I am not fully convinced whether the problems you recall are really COMMON-related.

Example 1: initialization of COMMON variables. ANSI Fortran 77 standard, sect. 8.3.5 (text boldfaced by me):

Entities in named common blocks may be initially defined by means of a DATA statement in a block data subprogram, but entities in blank common must not be initially defined

Example 2: mixing CHARACTER entities with other types in COMMONs. Ibidem, sect. 8.3.1:

If a character variable or character array is in a common block, all of the entities in that common block must be of type character.

I would say that using the compiler-specific extensions / inconsistencies to the Standard has never been a good idea, very error-prone.

The third example is most relevant. The Standard did not say anything about padding/alignment but did define partial and total storage association. So, if the sequence of types in the common block definitions was not identical, it was the user’s responsibility to use the objects right. Compilers (at least some of them) did warn when the definitions of common blocks differed due to padding but surely not in all cases was it possible. Still, the common practice of including the definitions was a pretty robust way to avoid such problems.

To conclude, I have nothing against the term error-prone assigned to common blocks if and only if it is given in the right context. If it is accompanied by a statement that in modern codes one should use modules instead but in the old days they were irreplaceable, then it is OK. Otherwise it makes me a bit nervous. We (the old coots like me) did not use common blocks for fun, out of stupidity but out of necessity.

2 Likes

The standard text in my opening comment in this thread had, " “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.”"

Note the phrase, " use of … ( COMMON ) statements was invaluable prior to Fortran 90 …"

Thus the context is clearly meant to be as you desire, that it pertains to the situation post Fortran 90 standard publication which itself now spans 30 years! But it pays respect to the circumstances during the earlier period where COMMON was acknowledged as being “invaluable”.

If we are discussing “error-prone”, one feature of “modern Fortran” that is “error-prone” is INTERFACE.
It has all the bad features of COMMON, in that INTERFACE code can be duplicated and there is little scope for most compilers to check for consistency between fortran files. Once set, INTERFACE can be an inactive definition that is not actively tested.
This can be especially so during program development, where many .f90 files are in use.

I once tried to overcome this problem, by placing all common INTERFACE definitions in an include file, similar to the approach for overcoming COMMON consistency, but you can’t include an interface in the actual routine. If this approach was allowed by the Fortran standard, this could provide an easier way for the compiler to check for inconsistent use of routines and their interface definition.

Again the alternative solution is to use modules and contain the related routines with the module, but this approach is not consistent with the use of libraries of routines, which has been a preferred way to build large programs.
There is an inconsistency between the way libraries have been used and modules containing routines. I have not seen discussion of this issue.
Any thoughts from other Fortran users ?

1 Like

Interfaces are very fragile indeed. Including the fact that they turn off the module’s implicit none and will use implicit typing…

The solution that I came to is to never use them, except in the following circumstances:

  • Interfacing f77 style code that does not use modules, such as Lapack. In there the interface to the subroutines does not change, so as long as I get it right once, it should keep working

  • Interfacing C using iso_c_binding. I wrote a Python script that takes the interface and generates a corresponding C header file which is then included with the C code, so the C compiler checks consistency. I would like LFortran to do that automatically, as my Python script is very fragile.

Regarding the design question of “libraries of routines”, why cannot you build a library using modules? That is my preferred approach and avoids this issue.

There can be problems with using library routines with modules, especially if the library is accessed via a dll.
With earlier 32-bit, I typically accessed libraries via .lib, but now with 64-bit, I just load the .o files.
It may simply be my lack of understanding of 64-bit linkers; trying to replicate what was done with 32-bit.
Am I wrong in interpreting 64-bit (generic) linkers do not easily support Fortran module libraries ?

Compilation of modern Fortran source files containing Fortran modules produces two sets of files: the .MOD files that will be used by the compiler when compiling other Fortran source files that have USE statements for the previously compiled Fortran modules, and the .OBJ files. At link time, only the .OBJ files will be used, along with any pre-built LIB files that are needed. Most linkers do nothing with .MOD files (confusion exists with the word “module”, because from the IBM 360 days it meant “load module”, which predates the nascence of Fortran “modules”). Similarly, most compilers do nothing with LIB or OBJ files when compiling. Some confusion exists w.r.t. compiling versus linking because modern compiler packages use a driver program that calls different phases/external programs in multiple passes (syntax parsing, optimization, code generation, linking, adding debug information, manifests, etc.) as needed.

Two different Fortran compilers, such as Intel Fortran and Gfortran on Windows, may be able to use the same OBJ and LIB files, such as those in the MKL or IMSL libraries, but one compiler cannot use the other’s MOD files. Generally, the ABI used in an OS sets the format of OBJ and LIB files. On the other hand, the compiler vendor may choose its own format for MOD files. Thus, along with a LIB file the developer of a library has to provide multiple sets of MOD files for use with different end user selected Fortran compilers, or may choose to provide dummy Fortran sources for the interfaces of the Fortran modules that the user can use to generate MOD files specific to the end user’s compiler.

That the language standard considers INTERFACE body declaring external subprograms as effectively a stand-alone construct is a needless limitation, I think. It comes across as a self-inflicted harm resulting out of the tussles during the tumultuous period prior to Fortran 90 release.

As many a reader will know, I feel strongly the path forward now will be to eliminate implicit mapping in a future revision (preferably Fortran 202Y) which will place Fortran on a more secure path forward. It will help with the INTERFACE situation as well.

1 Like

Having written this, readers not familiar with Fortran 2008 and later revisions should note the standard has tried to address the shortcomings when it comes to MODULE subprograms with SUBMODULEs a key aspect of separating the implementation from the interface and securitizing the implementation (to some extent).

Then with the use of Fortran 2008 and later revisions, @certik is correct that technically one can “build a library using modules”

What I mean by “technically” is “leave unto Fortran what pertains to Fortran” and keep apart the details pertaining to the processor.

Consider “library” code as follows: note it is standard Fortran, no processor-related details are brought in here.

module lib_m
   interface
      module subroutine libproc( n )
         integer, intent(in) :: n
      end subroutine
   end interface 
end module 
! Implementation may be in a separate file
submodule(lib_m) libproc_sm
contains
   module procedure libproc !<-- ensures implementation is consistent with its interface
      print *, "Hello World! The key is ", 42 + n
   end procedure 
end submodule 

Now consider the Windows situation mentioned by @mecej4 . The library author can do the processor-specific stuff by first defining what interfaces are consumable by the client in a `DEF file:

LIBRARY LIB
EXPORTS
   LIB_M_mp_LIBPROC         @1

Then following the processor-specific steps to “build a library” noting the Fortran program is in MODULEs only:

C:\Temp>ifort /c /standard-semantics lib.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

C:\Temp>link lib.obj /dll /subsystem:windows /def:lib.def /implib:lib.lib /out:lib.dll
Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.

Creating library lib.lib and object lib.exp

C:\Temp>

The library author then does one more processor-specific thingy: makes available to the client 3 files - the MOD, LIB, and DLL.

On the client side, the client has to now do processor-specific steps to consume the library, say as follows:

   use, intrinsic :: iso_c_binding, only : c_funloc, c_char, NUL => c_null_char, c_ptr, c_funptr,   &
                                           c_intptr_t, c_f_pointer, c_f_procpointer
   use IWin_m, only : LoadLibrary, GetProcAddress, GetDataAddress 
   use lib_m, only : Ilibproc => libproc !<-- USE the interface

   procedure(Ilibproc), pointer :: libproc => null() !<-- employ the interface

   blk_dll_load: block

      integer(c_intptr_t) :: m_handle
      character(kind=c_char, len=*), parameter :: DllName = c_char_"lib.dll" // NUL
      character(kind=c_char, len=*), parameter :: ProcName = c_char_"LIB_M_mp_LIBPROC" // NUL
      type(c_funptr) :: cfp_libproc

      m_handle = LoadLibrary( DllName )
      
      ! Set procedure pointer to user DLL method
      cfp_libproc = GetProcAddress( m_handle, ProcName )
      call c_f_procpointer( cfp_libproc, libproc )
      
   end block blk_dll_load

   call libproc( 1 ) !<-- A. Invoke library method with integer parameter
   !call libproc( 1.0 ) !<-- B. Invoke library method with real parameter

   stop

end

C:\Temp>ifort /c /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

C:\Temp>link p.obj lib.lib /subsystem:console /out:p.exe
Microsoft (R) Incremental Linker Version 14.29.30038.1
Copyright (C) Microsoft Corporation. All rights reserved.

C:\Temp>p.exe
Hello World! The key is 43

C:\Temp>

So one can see it is a series of details but it works ok. Now if the details are painstaking, then the root causes are related to 2 aspects: 1) Fortran defers a lot of things to the processor and 2) the processor (Windows-based in this example) may not make it all seamless and easy for a consumer. That is, the error prone aspects are not related to the base language all that much.

Separately, note the situation here is not all different with C or C++ or most other languages used on Windows.

In terms of Fortran itself, where the INTERFACE introduced starting Fortran 90 - which mimics to some extent the function prototypes in C and C++ - helps is when client fails to adhere to the vendor-client “contract” required by the INTERFACE: comment out line marked A and uncomment the one marked B in the above client code:

C:\Temp>ifort /c /standard-semantics p.f90
Intel(R) Fortran Intel(R) 64 Compiler Classic for applications running on Intel(R) 64, Version 2021.3.0 Build 20210609_000000
Copyright (C) 1985-2021 Intel Corporation. All rights reserved.

p.f90(76): error #6633: The type of the actual argument differs from the type of the dummy argument. [1.0]
call libproc( 1.0 ) !<-- B. Invoke library method with real parameter
-----------------^
compilation aborted for p.f90 (code 1)

C:\Temp>

TL;DR

  • With current Fortran, one can modernize library code considerably and bring about security and safety aspects and reduce overall errors during library consumption, this is especially true for scientific and technical computing libraries
  • The standard itself can try to advance by finally making implicit none the default; this will help with INTERFACE bodies a lot. And there are other such library development features the standard should add to the language also,
  • @certik’s vision of better tooling for Fortran is absolutely on the money for the standard for Fortran will inevitably leave a lot to the processor, thus the practitioners can benefit greatly by dealing with processor-specific details in the tooling.
1 Like

@garynewport This is exactly what led to the joke “God is REAL in FORTRAN unless declared otherwise” :laughing:

Distributing .mod files with a Fortran library is certainly a problem, but it doesn’t seem to be a reason that a “library of routines” is better than a library of modules. If you just omit the .mod files, isn’t it equivalent to a library of subprograms from the point of view of the consumer?

No, because most library subprograms intended to be used from a modern Fortran caller require explicit interfaces, and those explicit interfaces are provided by the ‘.mod’ files. Consider this example:

program tdot
use blas95, only : dot
real x(4),y(4),s
x = (/ 1.0, 2.0, 3.0, 4.0 /)
y = (/ 4.0, 3.0, 2.0, 1.0 /)
s = dot(x,y)
print *,s
end program

The generic name ‘dot’ does not even exist as an external symbol in the BLAS95 library. Try commenting out the USE statement and then building with a BLAS library or MKL.

Would it be of some help to use a module with just interfaces, to external (not module) subprograms? And build a classic library of those external subprograms compiled to object files.
I put a trivial sample

module interf
  interface
    subroutine sub(x,y)
      implicit none
      real, intent(inout) :: x,y
    end subroutine sub
  end interface
end module interf

program main
!  use interf
  real :: x, y
  integer :: i, j
  call sub(i,j)
end program main

subroutine sub(x,y)
  implicit none
  real, intent(inout) :: x,y
  real :: temp
  temp = x
  x = y
  y = temp
end subroutine sub

into three separate source files and compiled them successfully, so it seems a module may contain interfaces to external subprograms and serve as sort of include file.
Commenting out use interf in the main program results in compiler showing no error.