/[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.4 - (hide annotations) (download)
Tue Sep 29 18:50:56 1998 UTC (25 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint15
Changes since 1.3: +5 -1 lines
Changes for new exchange routines which do general tile <-> tile
connectivity, variable width overlap regions and provide
hooks for shared memory  and DMA protocols like Arctic, Memory Channel
etc..

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

  ViewVC Help
Powered by ViewVC 1.1.22