/[MITgcm]/MITgcm/eesupp/src/barrier.F
ViewVC logotype

Annotation of /MITgcm/eesupp/src/barrier.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.12 - (hide annotations) (download)
Mon Nov 7 18:16:08 2005 UTC (18 years, 7 months ago) by cnh
Branch: MAIN
Changes since 1.11: +21 -1 lines
Changes that enable OpenMP based threads.
Note - not all compute code is compatible with these.

1 cnh 1.12 C $Header: /u/u0/gcmpack/MITgcm/eesupp/src/barrier.F,v 1.11 2004/03/27 03:51:50 edhill Exp $
2 cnh 1.9 C $Name: $
3 cnh 1.1
4     #include "CPP_EEOPTIONS.h"
5    
6 cnh 1.9 CBOP
7     C !ROUTINE: BARRIER_INIT
8    
9     C !INTERFACE:
10 cnh 1.1 SUBROUTINE BARRIER_INIT
11 adcroft 1.6 IMPLICIT NONE
12 cnh 1.4
13 cnh 1.9 C !DESCRIPTION:
14     C *=====================================================================*
15 edhill 1.11 C | SUBROUTINE BARRIER\_INIT
16 cnh 1.9 C | o Setup global barrier data structures.
17     C *=====================================================================*
18     C | Initialise global barrier data structures that can be used in
19     C | conjunction with MPI or that can also be used to create
20     C *=====================================================================*
21    
22     C !USES:
23     C == Global variables ==
24 cnh 1.4 #include "SIZE.h"
25 cnh 1.1 #include "EEPARAMS.h"
26     #include "EESUPPORT.h"
27     #include "BARRIER.h"
28    
29 cnh 1.9 C !LOCAL VARIABLES:
30     C == Local Variables ==
31     C I :: Loop counter
32 cnh 1.1 INTEGER I
33 cnh 1.9 CEOP
34 cnh 1.1
35     DO I=1,nThreads
36     key1(1,I) = INVALID
37     key2(1,I) = INVALID
38     key3(1,I) = INVALID
39     door1 = SHUT
40     door2 = SHUT
41     door3 = SHUT
42 cnh 1.12 bCount(I) = 0
43 cnh 1.1 ENDDO
44    
45     RETURN
46     END
47 cnh 1.9
48     CBOP
49     C !ROUTINE: BARRIER
50    
51     C !INTERFACE:
52 cnh 1.1 SUBROUTINE BARRIER( myThid )
53     IMPLICIT NONE
54 cnh 1.4
55 cnh 1.9 C !DESCRIPTION:
56     C *==========================================================*
57     C | SUBROUTINE BARRIER
58     C | o Barrier routine that uses "busy waiting".
59     C *==========================================================*
60     C | This routine provides a pure fortran mechanism to
61     C | synchronise multiple threads in a multi-threaded code.
62     C | No thread can leave this routine before all the threads
63     C | have entered it.
64     C | Notes
65     C | =====
66     C | The door and key variables are assumed to have been
67     C | initialized once an initial state of key = INVALID
68     C | and door = SHUT.
69 edhill 1.11 C | We use the routine FOOL\_THE\_COMPILER to stop compilers
70 cnh 1.9 C | generating code which might simply set and test a
71     C | register value. Shared-memory systems only maintain
72     C | coherency over process caches and not registers.
73     C | Also we have to be a bit careful regarding sequential
74     C | consistency - or lack of it. At the moment the code
75     C | assumes a total store order memory model, which some
76     C | machines do not have! However, I have yet to find a
77     C | problem with this I think because the tolerances in
78     C | terms of memory ordering i.e. a little bit of reordering
79     C | probably will not break the barrier mechanism!
80     C | On non-cache coherent systems e.g. T3E we need to use
81     C | a library function to do barriers.
82     C | Note - The PANIC tests can be removed for working code
83     C | I have left them in without an ifdef option
84     C | because without them programming errors can
85     C | lead to infinitely spinning code. If you are
86     C | confident that your code is OK then removing
87     C | them may increase performance. Do not remove these
88     C | lines to make your code "work" If the code is
89     C | stopping in these PANIC blocks then something is
90     C | wrong with your program and it needs to be fixed.
91     C *==========================================================*
92    
93     C !USES:
94     C == Global variables ==
95 cnh 1.4 #include "SIZE.h"
96 cnh 1.1 #include "EEPARAMS.h"
97     #include "EESUPPORT.h"
98     #include "BARRIER.h"
99    
100 cnh 1.9 C !INPUT PARAMETERS:
101     C == Routine arguments ==
102 cnh 1.1 INTEGER myThid
103    
104 cnh 1.9 C !LOCAL VARIABLES:
105 cnh 1.1 C === Local variables ===
106 cnh 1.9 C nDone :: Counter for number of threads that have
107     C completed a section.
108     C I :: Loop counter
109 cnh 1.1 INTEGER nDone
110     INTEGER I
111 cnh 1.9 CEOP
112 cnh 1.1
113     CcnhDebugStarts
114 cnh 1.3 C WRITE(myThid,*) ' Barrier entered '
115 cnh 1.1 CcnhDebugEnds
116    
117 cnh 1.12 #ifdef USE_OMP_THREADING
118     C$OMP BARRIER
119     bCount(myThid) = bCount(myThid) + 1
120     Cdbg C$OMP BARRIER
121     Cdbg DO I=2, nThreads
122     Cdbg IF (bCount(I) .NE. bCount(1) ) THEN
123     Cdbg PRINT *, bCount(1:nThreads)
124     Cdbg CALL SYSTEM('sleep 1')
125     Cdbg PRINT *, bCount(1:nThreads)
126     Cdbg PRINT *, bCount(1:nThreads)
127     Cdbg PRINT *, bCount(1:nThreads)
128     Cdbg PRINT *, bCount(1:nThreads)
129     Cdbg STOP ' barrier out of sync '
130     Cdbg ENDIF
131     Cdbg ENDDO
132     Cdbg C$OMP BARRIER
133     RETURN
134     #endif
135    
136 cnh 1.1 C-- Check that thread number is expected range
137     IF ( myThid .LT. 1 .OR. myThid .GT. nThreads ) THEN
138 heimbach 1.8 WRITE(*,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
139     WRITE(*,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ',
140 cnh 1.5 & myThid, ' nThreads = ', nThreads
141 cnh 1.1 STOP 'ABNROMAL END: S/R BARRIER'
142     ENDIF
143    
144     C-- When every threads key1 is valid thread 1 will open door1.
145     IF ( key1(1,myThid) .EQ. VALID ) THEN
146 heimbach 1.8 WRITE(*,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
147     WRITE(*,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ',
148 cnh 1.5 & myThid, ' key1 already validated'
149 cnh 1.1 STOP 'ABNROMAL END: S/R BARRIER'
150     ENDIF
151     key1(1,myThid) = VALID
152    
153     IF ( myThid .eq. 1 ) THEN
154     10 CONTINUE
155     nDone = 0
156     DO I=1,nThreads
157     if ( key1(1,I) .EQ. VALID ) nDone = nDone+1
158     ENDDO
159     CALL FOOL_THE_COMPILER( key1 )
160     IF ( nDone .LT. nThreads ) GOTO 10
161     door1 = OPEN
162     ELSE
163     11 CONTINUE
164     CALL FOOL_THE_COMPILER( door1 )
165     IF ( door1 .NE. OPEN ) GOTO 11
166     ENDIF
167     C-- Invalidate keys for door1 here as it is now open
168     key1(1,myThid) = INVALID
169    
170     CcnhDebugStarts
171     C IF ( myThid .EQ. 1 ) THEN
172 heimbach 1.8 C WRITE(*,*) ' DOOR1 Opened '
173 cnh 1.1 C ENDIF
174     CcnhDebugEnds
175    
176     C-- I can now shut door3 because I know everyone has reached
177 adcroft 1.10 C-- door1. I can not shut door1 because I do not know if everyone
178 cnh 1.1 C-- has "gone" through the door yet. Nobody has yet reached
179     C-- door3 because they have to go through door2 first.
180     IF ( myThid .EQ. 1 ) THEN
181     door3 = SHUT
182     ENDIF
183    
184     C-- When every threads key2 is valid thread 1 will open door2.
185     C Notes
186     C =====
187     C I think that to work with any memory model ( i.e. relaxed,
188     C partial store, total store) the variables key1, key2 and key3
189     C might need to be set to invalid by thread 1.
190     C
191     IF ( key2(1,myThid) .EQ. VALID ) THEN
192 heimbach 1.8 WRITE(*,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
193     WRITE(*,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ',
194 cnh 1.5 & myThid, ' key2 already validated'
195 cnh 1.1 STOP 'ABNROMAL END: S/R BARRIER'
196     ENDIF
197     key2(1,myThid) = VALID
198     C
199     IF ( myThid .eq. 1 ) THEN
200     20 CONTINUE
201     nDone = 0
202     DO I=1,nThreads
203     if ( key2(1,I) .EQ. VALID ) nDone = nDone+1
204     ENDDO
205     CALL FOOL_THE_COMPILER( key2 )
206     IF ( nDone .LT. nThreads ) GOTO 20
207     door2 = OPEN
208     ELSE
209     21 CONTINUE
210     CALL FOOL_THE_COMPILER( door2 )
211     IF ( door2 .NE. OPEN ) GOTO 21
212     ENDIF
213    
214     C-- Invalidate keys for door2 here as it is now open
215     key2(1,myThid) = INVALID
216    
217     C-- I can now shut door1 because I know everyone has reached
218 adcroft 1.10 C-- door2. I can not shut door2 because I do not know if everyone
219 cnh 1.1 C-- has "gone" through the door yet. Nobody has yet reached
220     C-- door1 because they have to go through door3 first.
221     IF ( myThid .EQ. 1 ) THEN
222     door1 = SHUT
223     ENDIF
224    
225    
226     C-- When every threads key3 is valid thread 1 will open door3.
227     IF ( key3(1,myThid) .EQ. VALID ) THEN
228 heimbach 1.8 WRITE(*,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
229     WRITE(*,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ',
230 cnh 1.5 & myThid, ' key3 already validated'
231 cnh 1.1 STOP 'ABNROMAL END: S/R BARRIER'
232     ENDIF
233     key3(1,myThid) = VALID
234     C
235     IF ( myThid .eq. 1 ) THEN
236     30 CONTINUE
237     nDone = 0
238     DO I=1,nThreads
239     if ( key3(1,I) .EQ. VALID ) nDone = nDone+1
240     ENDDO
241     CALL FOOL_THE_COMPILER( key3 )
242     IF ( nDone .LT. nThreads ) GOTO 30
243     door3 = OPEN
244     ELSE
245     31 CONTINUE
246     CALL FOOL_THE_COMPILER( door3 )
247     IF ( door3 .NE. OPEN ) GOTO 31
248     ENDIF
249    
250     C-- Invalidate keys for door3 here as it is now open
251     key3(1,myThid) = INVALID
252    
253     C-- I can now shut door2 because I know everyone has reached
254 adcroft 1.10 C-- door3. I can not shut door3 because I do not know if everyone
255 cnh 1.1 C-- has "gone" through the door yet. Nobody has yet reached
256     C-- door2 because they have to go through door1 first.
257     IF ( myThid .EQ. 1 ) THEN
258     door2 = SHUT
259     ENDIF
260    
261     CcnhDebugStarts
262 cnh 1.3 C WRITE(myThid,*) ' Barrier exited '
263 cnh 1.1 CcnhDebugEnds
264    
265     RETURN
266     END

  ViewVC Help
Powered by ViewVC 1.1.22