/[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.6 - (hide annotations) (download)
Tue May 18 17:39:21 1999 UTC (25 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint28, checkpoint29, checkpoint22, checkpoint23, checkpoint24, checkpoint25, checkpoint27, branch-atmos-merge-freeze, branch-atmos-merge-start, checkpoint26, branch-atmos-merge-shapiro, checkpoint33, checkpoint32, checkpoint31, checkpoint30, checkpoint34, branch-atmos-merge-zonalfilt, branch-atmos-merge-phase5, branch-atmos-merge-phase4, branch-atmos-merge-phase7, branch-atmos-merge-phase6, branch-atmos-merge-phase1, branch-atmos-merge-phase3, branch-atmos-merge-phase2
Branch point for: branch-atmos-merge
Changes since 1.5: +2 -1 lines
Added IMPLICIT NONE where missing and changed formatting from 'I' to 'I5'.

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

  ViewVC Help
Powered by ViewVC 1.1.22