Intel® Fortran Compiler
Build applications that can scale for the future with optimized code designed for Intel® Xeon® and compatible processors.

Creating a thread-safe version of legacy F77 code containing common blocks

avinashs
New Contributor I
4,258 Views

Consider the situation where I have a set of Fortran 77 subroutines with one driver subroutine that represents a numerical method. These subroutines have many common blocks that share data and variables between them. I would like to make the common block information thread-safe. Is that possible with the following procedure:

(1) create a module subprogram in F90 but in a fixed source format file (*.for).
(2) paste the F77 subroutines in the module in the "contains" section.
(3) declare all the subroutines to be private
(4) write a public wrapper subroutine within the module that calls the driver.

An explanatory code is below (the calculations are only an example):

MODULE THREAD_SAFE_FUNCTION

      PRIVATE
      
      TYPE, PUBLIC :: MYVAR
      
      INTEGER :: N
      REAL :: S
      REAL, DIMENSION(:), ALLOCATABLE :: P

      CONTAINS

      PROCEDURE, PASS(SELF) :: DRIVER
      
      END TYPE MYVAR

      CONTAINS

      SUBROUTINE DRIVER(SELF,N,Y,S)
      CLASS(MYVAR) :: SELF
      INTEGER :: N
      REAL :: S,Y(N)
      SELF%N = N
      ALLOCATE(SELF%P(N))
      SELF%P = Y
      CALL TASK1(N,SELF%P,S)
      SELF%P=SELF%P**2
      END SUBROUTINE DRIVER

      SUBROUTINE TASK1(N,Y,S)
      COMMON /COM1/A,B,C  ! WANT COM1 AND COM2 TO BE THREAD-SAFE
      COMMON /COM2/Z(10)
      INTEGER N
      REAL S,Y(N)
      INTEGER I
      A=1
      B=2
      C=3
      DO I=1,N
         Z(I)=I
      ENDDO
      CALL TASK2(N,Y,S)
      RETURN
      END

      SUBROUTINE TASK2(N,X,S)
      COMMON /COM1/A,B,C
      COMMON /COM2/Z(10)
      INTEGER N
      REAL S,X(N,3)
      INTEGER I
C     SOME CALCULATIONS HERE
      A=2*A
      S=0.0D0
      DO I=1,N
         S=S+Z(I)**2
      ENDDO
      S=SQRT(S)
      RETURN
      END

      END MODULE THREAD_SAFE_FUNCTION

 

0 Kudos
8 Replies
TimP
Honored Contributor III
4,258 Views

When I invoke a search engine for the phrase "openmp common threadprivate" I get several excellent online references.  You may note that ifort has been more picky than most about where the common /threadprivate is placed and assuring that all instances of the COMMON match lengths..

0 Kudos
Arjen_Markus
Honored Contributor I
4,258 Views

There is no difference in facilities between fixed and free form - so your point (1) can be answered with "yes".

That said, modules are not about thread-safety and COMMON block simply cannot be made thread-safe.

But do not despair: you can use internal routines for the job, but in a slightly different way than you proposed:

! Driver routine calls the "master" routine 

call calculate_via_driver( ..., master_routine )

! master routine
subroutine master_routine( ... )
    implicit none
    integer :: x, y, z ! Originally defined in COMMON-block
    real :: a, b, c 
   
    ... preparations ...

    call step1
    call step2
    ...
contains
subroutine step1
     a = x + y  ! These are all defined in the master routine
end subroutine step1
subroutine step2
    b = 2.0 * a
end subroutine step2
end subroutine master_routine

The variables x, y, z, a, b, c are defined locally in the subroutine master_routine - you could have one instantiation in one thread and another in another thread and the actual memory locations for these variables would be completely independent, hence thread-safe.

The drawback of converting the COMMON blocks into local variables in an overall "master" routine is that they do not retain their values between calls. You can not use the SAVE attribute, because that would destroy the "localness". If you want to retain the values, use a derived type like you indicated:

  • Store these variables in this derived type (or object)
  • Copy their values into local variables at the start
  • Do the calculations
  • Copy the new values back in
  • Pass the derived type to the master routine as a dummy/actual argument - one actual, unique, argument for each thread

No time right now to provide a working example, but I hope the method is clear enough.

 

 

 

 

0 Kudos
Arjen_Markus
Honored Contributor I
4,258 Views

Hm, I forgot about that clause in OpenMP ... If you do use that method, it might be your simplest option.

0 Kudos
garylscott1
Beginner
4,258 Views

Common has been used for many decades in multithreaded and multiprocessor asynchronous parallel applications.  A typical method was to include a command/response communication interface.  So, no access was made until assigned the use of the area.  Once assigned, a thread or processor defined the content as required and then set a command or status response (bit) as appropriate to the operation performed and identified the operation expected by the recipient as required.  A simple handshaking approach is really pretty fast and only typically needed for a subset of communications that really need to be shared.  This also worked well for data capture, where a parallel processor filled a transfer buffer(s) while a second processor dumped the buffer(s) to a recording medium, preventing one getting ahead of the other or reusing a buffer that was in use or yet to be processed. 

So, common can work fine in a multithreaded environment with a tiny little bit of thought.  No, it won't happen naturally/natively.  But it can generally happen with far less overhead than many message passing schemes.

 

P.S. I guess I should clarify that I wasn't intending to advocate the use of common as a mechanism for setting up a shared memory area.  Only that the dangers of fixed shared memory buffers as a design approach are often vastly overstated.

0 Kudos
avinashs
New Contributor I
4,258 Views

Thanks for the useful responses. Hence, it appears that common statements in subroutines within modules are not guaranteed to be thread-safe although in practice they may work fine in a multithreaded environment. Using local variables with module scope as suggested is an alternative. However, (a) I want to avoid modifying code unless absolutely necessary and (2) in some cases, the common block variables do not have the same name i.e. /COM1/a,b,c in one subroutine and /COM1/x,y,z in another subroutine, which again makes modification complicated when you are working with legacy code.

0 Kudos
mecej4
Honored Contributor III
4,258 Views

I have seen worse problems with COMMON in old codes. Not only the names but even the types of the variables can be different in multiple declarations of COMMON in multiple subprograms. Sometimes, a common block variable has been initialized more than once using DATA statements. These kinds of lax usages can be quite troublesome even in a single-threaded program.

0 Kudos
jimdempseyatthecove
Honored Contributor III
4,258 Views

Try:

! threadprivate_COM.inc
COMMON /COM1/ A, B, C
!$OMP THREADPRIVATE( /COM1/)
REAL :: A, B, C

COMMON /COM2/ Z(10)
!$OMP THREADPRIVATE( /COM2/)
REAL :: Z
! end of file threadprivate_COM.inc
============================ new file ====
SUBROUTINE TASK1(N,Y,S)
! *** replace all instances COM1 and COM2 in all other files ***
INCLUDE 'threadprivate_COM.inc'
...

*** CAUTION ***

In older programs, quite often, a common block, say COM2 array Z, will get re-mapped with scalars or use differing names. You will have to sort this out using different files.

Also, assure that no global variables (visible to all threads) are included in the newly created thread private commons.

Jim Dempsey

0 Kudos
jimdempseyatthecove
Honored Contributor III
4,258 Views

Additionally,

I would (strongly) suggest replacing the COMMON blocks with data collections in MODULES. Modules can also have threadprivate entities. Note, you may still have issues of name conflicts, as well as data placement conflicts, should your same named common blocks have different mappings and/or types.

The most important first step is to insert IMPLICIT NONE in all procedures, and build your single threaded version, correct for undefined variables. When build succeeds, verify consistent results data, if not, correct.

Then migrate COMMONs to MODULEs, one file per named common, my preference is to pre-pend to the old common block name "mod_", e.g. mod_COM1 for COMMON /COM1/.

In the case where the former named common maps different names and/or types, a technique that can be used is to create a user defined type. Example:

! mod_COM1.F90
type COM1_t
  sequence
  union
    map
      real :: x, y, z
    end map
    map
      real :: alpha, beta, gamma
    end map
  end union
end type COM1_t

type(COM1_t) :: COM1
!$OMP THREADPRIVATE(COM1)

...

SUBROUTINE TASK1(N, Y, S)
  USE mod_COM1
  IMPLICIT NONE
  INTEGER :: N
  REAL :: Y, S
  ...
  COM1%A = 1  ! was A=1
  ...
  CALL TASK2(N, Y, S)
  ...
  CALL OTHER_SUB
...

SUBROUTINE TASK2(N, Y, S)
  USE mod_COM1
  IMPLICIT NONE
  INTEGER :: N
  REAL :: Y, S
  ...

  
SUBROUTINE OTHER_SUB
  USE mod_COM1
  IMPLICIT NONE
  ...
  COM1%alpha = 1 ! was alpha = 1
  ...

Now, expect a lot of flack

"Warning Will Robinson - unions are bad"

Jim Dempsey

0 Kudos
Reply