Common blocks without a name

What in the world is this?:

common xi(3),h(144)

Was that legal to have a common block with no name? Seems to compile fine with gfortran.

The use of un-named common was a pre-F90 feature that this common block was placed at the “end of memory” by the linker.
This could have been used (in batch runs) to address extended available memory, beyond what is allocated to the program during the link/build. It was a way of getting extra memory, before ALLOCATE was available.

Now with extendable heap, this may no longer be true. The use of ALLOCATE to extend available memory is a much better approach.

I tried the following program on Win x64 with Gfortran and FTN95.
The GByte memory addresses show “liberal” use of virtual memory, far greater than physical memory.

Gfortran places blank common at the end of memory.
But not FTN95, although it provides an 8 GByte buffer !

program array_test

  common xi,h
  common /jj/ xj,hj
  real xi(3),h(144),xj(3),hj(144)

  real :: A(10), x
  real, allocatable :: B1(:), B2(:)
  integer*8 :: gbyte = 2**30

  allocate ( B1(gbyte) )
  allocate ( B2(gbyte) )

  call report_memory ( 'xi', loc(xi), ' blank COMMON' )
  call report_memory ( 'xj', loc(xj), ' labeled COMMON jj' )
  call report_memory ( 'A ', loc(A), ' local stack array' )
  call report_memory ( 'B1', loc(B1), ' Allocated heap array' )
  call report_memory ( 'B2', loc(B2), ' Allocated heap array' )
  call report_memory ( 'x ', loc(x), ' local stack variable' )

  A = 0

 contains

    subroutine f(n, A)
     integer :: n
     real, intent(inout) :: A(n)
     A(n) = 1
    end subroutine

    subroutine report_memory ( variable_name, variable_loc, description )
     character*(*) :: variable_name, description
     integer*8 :: variable_loc, gb_address
     integer*8 :: gbyte = 2**30

     gb_address = variable_loc / gbyte
     write (*,*) variable_name, gb_address, variable_loc, description

    end subroutine report_memory 
    
end program
1 Like

“Blank COMMON”. Special rules for blank COMMON compared to labelled COMMON. Some early Fortran implementations had “Numbered COMMON”. Members of labelled COMMON can be initialized in BLOCK DATA program units. On old mainframes, blank common was made available after the program was linked and loaded (reusing memory used earlier during linking), so blank common variables could not be initialized.

I’ll also note that blank common is exempt from the rule that the common must be the same length in all program units where it appears.

2 Likes