/[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.2 - (hide annotations) (download)
Thu Apr 23 20:37:29 1998 UTC (26 years, 1 month ago) by cnh
Branch: MAIN
CVS Tags: redigm, checkpoint5, checkpoint4, checkpoint6, checkpoint1, checkpoint3, checkpoint2, kloop1, kloop2
Changes since 1.1: +1 -3 lines
Changed $Id to $Header

1 cnh 1.2 C $Header: barrier.F,v 1.1.1.1 1998/04/22 19:15:30 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     C IF ( myThid .EQ. 1 ) THEN
79     C WRITE(0,*) ' Barrier entered '
80     C ENDIF
81     CcnhDebugEnds
82    
83     C-- Check that thread number is expected range
84     IF ( myThid .LT. 1 .OR. myThid .GT. nThreads ) THEN
85     WRITE(0,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
86     WRITE(0,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ', myThid, ' nThreads = ', nThreads
87     STOP 'ABNROMAL END: S/R BARRIER'
88     ENDIF
89    
90     C-- When every threads key1 is valid thread 1 will open door1.
91     IF ( key1(1,myThid) .EQ. VALID ) THEN
92     WRITE(0,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
93     WRITE(0,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ', myThid, ' key1 already validated'
94     STOP 'ABNROMAL END: S/R BARRIER'
95     ENDIF
96     key1(1,myThid) = VALID
97    
98     IF ( myThid .eq. 1 ) THEN
99     10 CONTINUE
100     nDone = 0
101     DO I=1,nThreads
102     if ( key1(1,I) .EQ. VALID ) nDone = nDone+1
103     ENDDO
104     CALL FOOL_THE_COMPILER( key1 )
105     IF ( nDone .LT. nThreads ) GOTO 10
106     door1 = OPEN
107     ELSE
108     11 CONTINUE
109     CALL FOOL_THE_COMPILER( door1 )
110     IF ( door1 .NE. OPEN ) GOTO 11
111     ENDIF
112     C-- Invalidate keys for door1 here as it is now open
113     key1(1,myThid) = INVALID
114    
115     CcnhDebugStarts
116     C IF ( myThid .EQ. 1 ) THEN
117     C WRITE(0,*) ' DOOR1 Opened '
118     C ENDIF
119     CcnhDebugEnds
120    
121     C-- I can now shut door3 because I know everyone has reached
122     C-- door1. I can't shut door1 because I don't know if everyone
123     C-- has "gone" through the door yet. Nobody has yet reached
124     C-- door3 because they have to go through door2 first.
125     IF ( myThid .EQ. 1 ) THEN
126     door3 = SHUT
127     ENDIF
128    
129     C-- When every threads key2 is valid thread 1 will open door2.
130     C Notes
131     C =====
132     C I don't understand memory ordering and sequential consistency.
133     C I think that to work with any memory model ( i.e. relaxed,
134     C partial store, total store) the variables key1, key2 and key3
135     C might need to be set to invalid by thread 1.
136     C
137     IF ( key2(1,myThid) .EQ. VALID ) THEN
138     WRITE(0,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
139     WRITE(0,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ', myThid, ' key2 already validated'
140     STOP 'ABNROMAL END: S/R BARRIER'
141     ENDIF
142     key2(1,myThid) = VALID
143     C
144     IF ( myThid .eq. 1 ) THEN
145     20 CONTINUE
146     nDone = 0
147     DO I=1,nThreads
148     if ( key2(1,I) .EQ. VALID ) nDone = nDone+1
149     ENDDO
150     CALL FOOL_THE_COMPILER( key2 )
151     IF ( nDone .LT. nThreads ) GOTO 20
152     door2 = OPEN
153     ELSE
154     21 CONTINUE
155     CALL FOOL_THE_COMPILER( door2 )
156     IF ( door2 .NE. OPEN ) GOTO 21
157     ENDIF
158    
159     C-- Invalidate keys for door2 here as it is now open
160     key2(1,myThid) = INVALID
161    
162     C-- I can now shut door1 because I know everyone has reached
163     C-- door2. I can't shut door2 because I don't know if everyone
164     C-- has "gone" through the door yet. Nobody has yet reached
165     C-- door1 because they have to go through door3 first.
166     IF ( myThid .EQ. 1 ) THEN
167     door1 = SHUT
168     ENDIF
169    
170    
171     C-- When every threads key3 is valid thread 1 will open door3.
172     IF ( key3(1,myThid) .EQ. VALID ) THEN
173     WRITE(0,*) '!!!!!!! PANIC !!!!!!! CATASTROPHIC ERROR'
174     WRITE(0,*) '!!!!!!! PANIC !!!!!!! in S/R BARRIER myThid = ', myThid, ' key3 already validated'
175     STOP 'ABNROMAL END: S/R BARRIER'
176     ENDIF
177     key3(1,myThid) = VALID
178     C
179     IF ( myThid .eq. 1 ) THEN
180     30 CONTINUE
181     nDone = 0
182     DO I=1,nThreads
183     if ( key3(1,I) .EQ. VALID ) nDone = nDone+1
184     ENDDO
185     CALL FOOL_THE_COMPILER( key3 )
186     IF ( nDone .LT. nThreads ) GOTO 30
187     door3 = OPEN
188     ELSE
189     31 CONTINUE
190     CALL FOOL_THE_COMPILER( door3 )
191     IF ( door3 .NE. OPEN ) GOTO 31
192     ENDIF
193    
194     C-- Invalidate keys for door3 here as it is now open
195     key3(1,myThid) = INVALID
196    
197     C-- I can now shut door2 because I know everyone has reached
198     C-- door3. I can't shut door3 because I don't know if everyone
199     C-- has "gone" through the door yet. Nobody has yet reached
200     C-- door2 because they have to go through door1 first.
201     IF ( myThid .EQ. 1 ) THEN
202     door2 = SHUT
203     ENDIF
204    
205     CcnhDebugStarts
206     C IF ( myThid .EQ. 1 ) THEN
207     C WRITE(0,*) ' Barrier exited '
208     C ENDIF
209     CcnhDebugEnds
210    
211     RETURN
212     END

  ViewVC Help
Powered by ViewVC 1.1.22