I’ve inherited an OpenMP-threaded codebase that has a module looking something like this
module m
implicit none
public
real, private :: table(100)
logical, private :: table_init
!$OMP threadprivate(table, table_init)
contains
subroutine init_table
integer :: i
table(1) = 1.0
do i = 2, size(table)
table(i) = real(i)*table(i-1)/real(128)
end do
table_init = .true.
end subroutine
real function f(n, x)
integer, intent(in) :: n
real, intent(in) :: x
if (.not. table_init) call init_table
f = table(n)*x**n
end function
end module m
That is, there is a function which uses a lookup table stored as a module variable, along with a flag to keep track of whether or not it’s been initialized. Thread safety is maintained by giving each thread a private copy of the lookup table.
However, in this example as well as in the real code, the table is not modified after initialization. The table and its initialization flag can be safely shared across threads, as long as I make sure that only one thread initializes the table, and all other threads wait to read from the table until the initialization flag is set. I’m looking for help implementing this logic.
The crudest thing that comes to is to remove the threadprivate
directive in the module, remove the initialization check from f
, and explicitly fill the array in the main program like so:
module m
implicit none
public
real, private :: table(100)
logical, private :: table_init
contains
subroutine init_table
integer :: i
table(1) = 1.0
do i = 2, size(table)
table(i) = real(i)*table(i-1)/real(128)
end do
table_init = .true.
end subroutine
real function f(n, x)
integer, intent(in) :: n
real, intent(in) :: x
! assumes table is initialized
f = table(n)*x**n
end function
end module m
program p
use m
implicit none
!$OMP single
call init_table
!$OMP end single
!$OMP barrier
! .... rest of the program
end program
That should work, I think, but it makes code maintenance more difficult. I’d really like to keep all the table management logic confined to the module. For reference, the function f
will be called very frequently, so putting heavy thread synchronization logic in there is unappealing. I’m not super OpenMP-literate, have I overlooked some facility that would help here?