/[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.3 - (hide annotations) (download)
Wed Jun 10 17:05:59 1998 UTC (25 years, 11 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint11, checkpoint10, checkpoint13, checkpoint14, checkpoint7, checkpoint9, checkpoint8, checkpoint12, branch-point-rdot
Branch point for: checkpoint7-4degree-ref, branch-rdot
Changes since 1.2: +3 -7 lines
Minor changes to correct bugs with multi-process mode
of operation

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

  ViewVC Help
Powered by ViewVC 1.1.22