- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hi,
I need to use a shared variable between threads (global_lock) in this case
IF(master_thread) THEN
global_lock=local_lock
ELSE
DO WHILE(local_lock .NE. global_lock)
ENDDO
ENDIF
if global_lock is declared INTEGER,VOLATILE :: global_lock
I haven't any problem but when I try to use global_lock like a array, for example
INTEGER,VOLATILE :: global_lock(16)
or
INTEGER,VOLATILE,DIMENSION(16) :: global_lock
or
INTEGER :: global_lock(16)
VOLATILE global_lock
or
INTEGER,VOLATILE :: global_lock(1:16)
and even!!!!
INTEGER,VOLATILE,DIMENSION(1) :: global_lock
Optimization Options(O2) eliminates the DOWHILE loop, but if I use INTEGER,VOLATILE :: global_lock, compile doesn't eliminate the DOWHILE loop, Intel fortran Manual explains that If an array is declared VOLATILE, each element in the array becomes volatile.
Also, I have added one instruction inside DOWHILE loop, in this case Optimization options doesn't eliminate the DOWHILE loop but all threads(less master_thread) stay locked in the loop DOWHILE, I imagine because the threads don't access to memory to ckeck the new valor of global_lock, and in this case too, if global_lock isn't an array i haven't problem.
I don't want to change method but I need that global_lock will be a VOLATILE array, what can I do?
Thanks!!!!
Mario.
I need to use a shared variable between threads (global_lock) in this case
IF(master_thread) THEN
global_lock=local_lock
ELSE
DO WHILE(local_lock .NE. global_lock)
ENDDO
ENDIF
if global_lock is declared INTEGER,VOLATILE :: global_lock
I haven't any problem but when I try to use global_lock like a array, for example
INTEGER,VOLATILE :: global_lock(16)
or
INTEGER,VOLATILE,DIMENSION(16) :: global_lock
or
INTEGER :: global_lock(16)
VOLATILE global_lock
or
INTEGER,VOLATILE :: global_lock(1:16)
and even!!!!
INTEGER,VOLATILE,DIMENSION(1) :: global_lock
Optimization Options(O2) eliminates the DOWHILE loop, but if I use INTEGER,VOLATILE :: global_lock, compile doesn't eliminate the DOWHILE loop, Intel fortran Manual explains that If an array is declared VOLATILE, each element in the array becomes volatile.
Also, I have added one instruction inside DOWHILE loop, in this case Optimization options doesn't eliminate the DOWHILE loop but all threads(less master_thread) stay locked in the loop DOWHILE, I imagine because the threads don't access to memory to ckeck the new valor of global_lock, and in this case too, if global_lock isn't an array i haven't problem.
I don't want to change method but I need that global_lock will be a VOLATILE array, what can I do?
Thanks!!!!
Mario.
Link Copied
12 Replies
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
As a work around
type iv
integer, volatile :: lock
end type iv
type(iv) :: global_lock(16)
...
do i=1,size(global_lock)
global_lock(i)%lock = 0
end do
...
IF(master_thread) THEN
global_lock(i)%lock=local_lock ! or local_lock(i)%lock
ELSE
DO WHILE(local_lock .NE. global_lock(i)%lock)
ENDDO
ENDIF
...
Jim Dempsey
type iv
integer, volatile :: lock
end type iv
type(iv) :: global_lock(16)
...
do i=1,size(global_lock)
global_lock(i)%lock = 0
end do
...
IF(master_thread) THEN
global_lock(i)%lock=local_lock ! or local_lock(i)%lock
ELSE
DO WHILE(local_lock .NE. global_lock(i)%lock)
ENDDO
ENDIF
...
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Have you considered using the Fortran standard lock support? This uses the LOCK_TYPE declared in intrinsic module ISO_FORTRAN_ENV and the LOCK and UNLOCK statements.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Note that the LOCK_TYPE in Fortran is meant for use in the context of coarrays - if the OP really desires threading as indicated, then this facility will not help.
If the threading used by OP is OpenMP, then an integer(omp_lock_kind) should be used, and the associated locking functions omp_init_lock, omp_lock, omp_unlock etc.
If the threading is done with POSIX threads, I think similar facilities are available in the pthreads library.
Regards
Reinhold
If the threading used by OP is OpenMP, then an integer(omp_lock_kind) should be used, and the associated locking functions omp_init_lock, omp_lock, omp_unlock etc.
If the threading is done with POSIX threads, I think similar facilities are available in the pthreads library.
Regards
Reinhold
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Firstly, thanks for your suggestions
Use a Type variable was hopeful but compiler give a error very clear with this
type iv
INTEGER, VOLATILE ::lock
end type iv
type(iv) :: global_lock(16)
error #6516: This attribute specification is not valid for a component definition statement. [VOLATILE]
INTEGER, VOLATILE ::lock
Secondly, I am using OpenMP(Intel Fortran 11.1) and I imagine that I can use omp_set_lock and omp_unset_lock to solve the problem but really the portion of code that I have showed is to a special barrier to NUMA Architecture, I try to improve performance to the maximum I think that if I use omp_set_lock and omp_unset_lock, I will increment the number of instructions.
For this reason I would appreciate a lot if someone can give me a solution using VOLATILE and arrays or at least something that does not change the method used (with a loop DOWHILE)
Regards
Mario Acosta
PhD Student
Use a Type variable was hopeful but compiler give a error very clear with this
type iv
INTEGER, VOLATILE ::lock
end type iv
type(iv) :: global_lock(16)
error #6516: This attribute specification is not valid for a component definition statement. [VOLATILE]
INTEGER, VOLATILE ::lock
Secondly, I am using OpenMP(Intel Fortran 11.1) and I imagine that I can use omp_set_lock and omp_unset_lock to solve the problem but really the portion of code that I have showed is to a special barrier to NUMA Architecture, I try to improve performance to the maximum I think that if I use omp_set_lock and omp_unset_lock, I will increment the number of instructions.
For this reason I would appreciate a lot if someone can give me a solution using VOLATILE and arrays or at least something that does not change the method used (with a loop DOWHILE)
Regards
Mario Acosta
PhD Student
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Mario,
I should have tried the type with volatile here before suggesting this
Steve... what is the reasoning behind this?
Mario,
I do not have my Linux system up and running now. Lookin the runtime library (USE xxx) for atomic functions. OnWindowsthey are in KERNEL32.MOD.
InterlockedExchange
InterlockedCompareExchange
InterlockedIncrement
InterlockedDecrement
...
These functions take type LONG
The Linux library should have analogs to these. You can wrap these in a wrapper function to improve portability (e.g. CAS, XCHG, XADD, ...)
Jim Dempsey
I should have tried the type with volatile here before suggesting this
Steve... what is the reasoning behind this?
Mario,
I do not have my Linux system up and running now. Lookin the runtime library (USE xxx) for atomic functions. OnWindowsthey are in KERNEL32.MOD.
InterlockedExchange
InterlockedCompareExchange
InterlockedIncrement
InterlockedDecrement
...
These functions take type LONG
The Linux library should have analogs to these. You can wrap these in a wrapper function to improve portability (e.g. CAS, XCHG, XADD, ...)
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
You cannot declare a component of a derived type to be VOLATILE. You can declare whole variables to be VOLATILE.
Those atomic functions you reference do not exist for Linux.
Sorry for the goof on suggesting LOCK_TYPE. Indeed that is for coarrays only.
Those atomic functions you reference do not exist for Linux.
Sorry for the goof on suggesting LOCK_TYPE. Indeed that is for coarrays only.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
>>You cannot declare a component of a derived type to be VOLATILE.
Do you know why the standards committee chose to do this?
>> You can declare whole variables to be VOLATILE
The following seems to work (at least here)
Note, volatile array of user defined type
Jim Dempsey
Do you know why the standards committee chose to do this?
>> You can declare whole variables to be VOLATILE
The following seems to work (at least here)
[cpp]program asdf type iv sequence INTEGER :: LOCK end type iv type(iv), VOLATILE :: global_lock(16) integer :: i do i=1,16 global_lock(i)%lock = irand() end do write(*,*) 'here' if(global_lock(2)%lock .eq. 0) then if(global_lock(2)%lock .eq. 0) then stop 'here' endif endif end program asdf[/cpp]
Note, volatile array of user defined type
[bash] if(global_lock(2)%lock .eq. 0) then 0040112A mov eax,dword ptr [GLOBAL_LOCK+4 (4D6604h)] 0040112F test eax,eax 00401131 jne ASDF+168h (401168h) if(global_lock(2)%lock .eq. 0) then 00401133 mov eax,dword ptr [GLOBAL_LOCK+4 (4D6604h)] 00401138 test eax,eax 0040113A jne ASDF+168h (401168h) [/bash]
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
It's hard to know "why" something was done, but it would not be in the spirit of type declarations to add something like VOLATILE in there. VOLATILE is a variable attribute. Sure, I can imagine such a definition but it doesn't really fit cleanly. You can't say that a component is ASYNCHRONOUS either.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
>>It's hard to know "why" something was done
Unless you served on the standards committee....
>>but it would not be in the spirit of type declarations to add something like VOLATILE in there
type foo
type(foo), pointer :: next
integer, volatile :: lockFlag
integer :: this, that, another
real :: ding, dong
end type foo
What is not "in the spirit of type declarations" by making lockFlag volatile???
While you can certainly use:
wasLocked = InterlockedExchange(node%lockFlag, 1)
To test and set, you have no simple means of test alone without volatile. While test within a non-inlined function may return the current value, statements that may get inlined or optimized will not make the (re)read of the memory variable at the logical point in the code as represented in the source. The use of VOLATILE will (should) enforce re-read of memory.
Jim Dempsey
Unless you served on the standards committee....
>>but it would not be in the spirit of type declarations to add something like VOLATILE in there
type foo
type(foo), pointer :: next
integer, volatile :: lockFlag
integer :: this, that, another
real :: ding, dong
end type foo
What is not "in the spirit of type declarations" by making lockFlag volatile???
While you can certainly use:
wasLocked = InterlockedExchange(node%lockFlag, 1)
To test and set, you have no simple means of test alone without volatile. While test within a non-inlined function may return the current value, statements that may get inlined or optimized will not make the (re)read of the memory variable at the logical point in the code as represented in the source. The use of VOLATILE will (should) enforce re-read of memory.
Jim Dempsey
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
lockFlag in your example is not a variable. It is a component in a derived type declaration.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
Hello,
I have tried
typeiv
sequence
INTEGER::LOCK
endtypeiv
type(iv),VOLATILE::global_lock(16)
but i have same problem that with
INTEGER, VOLATILE, global_lock(16)
Compiler elimines DOWHILE loop with -O2
Now, I have tried to insert DOWHILE loop with inline assembler(using ISO_C_BINDING and asm)
This would be DOWHILE that I want to insert
DO WHILE((banderaglobal(numsocket) /= banderalocal) .EQ. .TRUE.)
ENDDO
and this the Subroutine that I have used:
call insertwhile(banderaglobal(numsocket),numsocket,banderalocal)
where insertwhile is
subroutine insertwhile(banderaglobal,numsocket,banderalocal) bind(C)
use iso_c_binding, only: c_int
integer(c_int),volatile :: banderaglobal
integer(c_int) :: numsocket
integer(c_int) :: banderalocal
end subroutine
and C subroutine
void insertwhile(int volatile *banderaglobal,int *numsocket,int *banderalocal)
{
__asm__ __volatile__("movl (%0),%%eax\n"
"1:\n\t"
"cmpl (%1),%%eax\n\t"
"jne 1\n\t"
:
:"r" (banderalocal),"r" (banderaglobal)
:"%eax");
}
But again... I have a problem with this, a segmentation fault when i run program, I know that segmentation fault is produced in the loop that I have created and is very curious because if I delete only "jne 1\n\t" I haven't any segmentation fault, I want to say that if I acces only one time, instruction compl is correct, but if this is a loop I obtain a segmentation fault in some time with instruction compl.
I have tried
typeiv
sequence
INTEGER::LOCK
endtypeiv
type(iv),VOLATILE::global_lock(16)
but i have same problem that with
INTEGER, VOLATILE, global_lock(16)
Compiler elimines DOWHILE loop with -O2
Now, I have tried to insert DOWHILE loop with inline assembler(using ISO_C_BINDING and asm)
This would be DOWHILE that I want to insert
DO WHILE((banderaglobal(numsocket) /= banderalocal) .EQ. .TRUE.)
ENDDO
and this the Subroutine that I have used:
call insertwhile(banderaglobal(numsocket),numsocket,banderalocal)
where insertwhile is
subroutine insertwhile(banderaglobal,numsocket,banderalocal) bind(C)
use iso_c_binding, only: c_int
integer(c_int),volatile :: banderaglobal
integer(c_int) :: numsocket
integer(c_int) :: banderalocal
end subroutine
and C subroutine
void insertwhile(int volatile *banderaglobal,int *numsocket,int *banderalocal)
{
__asm__ __volatile__("movl (%0),%%eax\n"
"1:\n\t"
"cmpl (%1),%%eax\n\t"
"jne 1\n\t"
:
:"r" (banderalocal),"r" (banderaglobal)
:"%eax");
}
But again... I have a problem with this, a segmentation fault when i run program, I know that segmentation fault is produced in the loop that I have created and is very curious because if I delete only "jne 1\n\t" I haven't any segmentation fault, I want to say that if I acces only one time, instruction compl is correct, but if this is a loop I obtain a segmentation fault in some time with instruction compl.
Sorry to ask again, I appreciate any suggestions with this or some solutions with VOLATILE arrays
or maybe Is there any possibility that the compiler does not optimize a block of code in fortran?
Regards,
Mario.
or maybe Is there any possibility that the compiler does not optimize a block of code in fortran?
Regards,
Mario.
- Mark as New
- Bookmark
- Subscribe
- Mute
- Subscribe to RSS Feed
- Permalink
- Report Inappropriate Content
I reply me,
If I change "jne 1\n\t" --> "jne 1b\n\t", program run and my new barrier works perfectly
even so, I keep thanking any suggestions where I haven't to use inline assembler and ISO_C_BINDING
Regars,
Mario.
If I change "jne 1\n\t" --> "jne 1b\n\t", program run and my new barrier works perfectly
even so, I keep thanking any suggestions where I haven't to use inline assembler and ISO_C_BINDING
Regars,
Mario.

Reply
Topic Options
- Subscribe to RSS Feed
- Mark Topic as New
- Mark Topic as Read
- Float this Topic for Current User
- Bookmark
- Subscribe
- Printer Friendly Page