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

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

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


Revision 1.23 - (hide annotations) (download)
Sat Nov 5 00:51:06 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58b_post, checkpoint57y_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint58d_post, checkpoint58a_post, checkpoint57z_post, checkpoint58y_post, checkpoint58t_post, checkpoint58m_post, checkpoint58w_post, checkpoint57y_pre, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58r_post, checkpoint58n_post, checkpoint59p, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint58g_post, checkpoint58x_post, checkpoint59j, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint57x_post, checkpoint58c_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.22: +2 -9 lines
move local commom bloc /GlobalLo/ in EESUPPORT.h

1 jmc 1.23 C $Header: /u/gcmpack/MITgcm/eesupp/src/ini_procs.F,v 1.22 2005/02/18 19:43:27 ce107 Exp $
2 adcroft 1.13 C $Name: $
3 cnh 1.1 #include "CPP_EEOPTIONS.h"
4 cnh 1.14 CBOP
5    
6     C !ROUTINE: INI_PROCS
7    
8     C !INTERFACE:
9 cnh 1.1 SUBROUTINE INI_PROCS
10 adcroft 1.10 IMPLICIT NONE
11 cnh 1.1
12 cnh 1.14 C !DESCRIPTION:
13     C *==========================================================*
14 edhill 1.18 C | SUBROUTINE INI\_PROCS
15 cnh 1.14 C | o Initialise multiple concurrent processes environment.
16     C *==========================================================*
17     C | Under MPI this routine calls various MPI service routines
18     C | that map the model grid to MPI processes. The information
19     C | is then stored in a common block for later use.
20     C | Note: This routine can also be compiled with CPP
21     C | directives set so that no multi-processing is initialise.
22     C | This is OK and should work fine.
23     C *==========================================================*
24    
25     C !USES:
26 cnh 1.1 C === Global data ===
27     #include "SIZE.h"
28     #include "EEPARAMS.h"
29     #include "EESUPPORT.h"
30    
31 cnh 1.14 C !LOCAL VARIABLES:
32 cnh 1.1 C === Local variables ===
33     #ifdef ALLOW_USE_MPI
34 cnh 1.14 C msgBuffer :: IO buffer
35     C myThid :: Dummy thread id
36     C mpiRC :: Error code reporting variable used
37     C with MPI.
38     C mpiGridSpec :: No. of processes in X and Y.
39     C mpiPeriodicity :: Flag indicating XY priodicity to MPI.
40     C arrElSize :: Size of an array element in bytes used
41     C to define MPI datatypes for communication
42     C operations.
43     C arrElSep :: Separation in units of array elements between
44     C blocks to be communicated.
45     C elCount :: No. of blocks that are associated with MPI
46     C datatype.
47     C elLen :: Length of an MPI datatype in terms of preexisting
48     C datatype.
49     C elStride :: Distance between starting location of elements
50     C in an MPI datatype - can be bytes of datatype
51     C units.
52 cnh 1.1 CHARACTER*(MAX_LEN_MBUF) msgBuffer
53     INTEGER mpiRC
54     INTEGER mpiGridSpec(2)
55     INTEGER mpiPeriodicity(2)
56     INTEGER mpiLProcNam
57     CHARACTER*(MPI_MAX_PROCESSOR_NAME) mpiProcNam
58     INTEGER arrElSize
59     INTEGER arrElSep
60     INTEGER elCount
61     INTEGER elLen
62     INTEGER elStride
63 dimitri 1.20 INTEGER npe,itemp,ierr,istatus(MPI_STATUS_SIZE)
64     INTEGER mpiBufSize,mpiRequest
65     #endif /* ALLOW_USE_MPI */
66     INTEGER myThid
67 cnh 1.14 CEOP
68 cnh 1.1
69     C-- Default values set to single processor case
70 cnh 1.7 C pid[W-SE] are the MPI process id of the neighbor
71 cnh 1.1 C processes. A process can be its own neighbor!
72 cnh 1.6 myThid = 1
73     myPid = 1
74     nProcs = 1
75     myPx = 1
76     myPy = 1
77     myXGlobalLo = 1
78     myYGlobalLo = 1
79     pidW = 1
80     pidE = 1
81     pidN = 1
82     pidS = 1
83 adcroft 1.17 c errorMessageUnit = 0
84     c standardMessageUnit = 6
85 cnh 1.6
86 cnh 1.1 #ifdef ALLOW_USE_MPI
87     C--
88     C-- MPI style full multiple-process initialisation
89     C-- ==============================================
90     #ifndef ALWAYS_USE_MPI
91     IF ( usingMPI ) THEN
92     #endif
93    
94     C-- Arrange MPI processes on a cartesian grid
95     C Set variable indicating which MPI process is to the north,
96     C south, east, west, south-west, south-east, north-west
97     C and north-east of me e.g.
98     C
99     C Plan view of model domain centered on process ME
100     C ================================================
101     C
102     C : : : :
103     C : : : :
104     C : : : :
105     C .....------------------------------.....
106     C | | | |
107     C | NW | N | NE |
108     C | | | |
109     C .....------------------------------.....
110     C | | | |
111     C | W | ME | E |
112     C | | | |
113     C .....------------------------------.....
114     C | | | |
115     C | SW | S | SE |
116     C | | | |
117     C .....------------------------------.....
118     C : : : :
119     C Y : : : :
120     C / \ : : : :
121     C |
122     C |
123     C |----> X
124     C
125     C-- Set default MPI communicator to XY processor grid
126     myThid = 1
127     mpiGridSpec(1) = nPx
128     mpiGridSpec(2) = nPy
129     C Could be periodic in X and/or Y - set at run time or compile time!
130     mpiPeriodicity(1) = _mpiTRUE_
131     mpiPeriodicity(2) = _mpiTRUE_
132     #ifdef CAN_PREVENT_X_PERIODICITY
133     #ifndef ALWAYS_PREVENT_X_PERIODICITY
134     IF ( notUsingXPeriodicity ) THEN
135     #endif
136     mpiPeriodicity(1) = _mpiFALSE_
137     #ifndef ALWAYS_PREVENT_X_PERIODICITY
138     ENDIF
139     #endif
140     #endif /* CAN_PREVENT_X_PERIODICITY */
141     #ifdef CAN_PREVENT_Y_PERIODICITY
142     #ifndef ALWAYS_PREVENT_Y_PERIODICITY
143     IF ( notUsingYPeriodicity ) THEN
144     #endif
145     mpiPeriodicity(2) = _mpiFALSE_
146     #ifndef ALWAYS_PREVENT_Y_PERIODICITY
147     ENDIF
148     #endif
149     #endif /* CAN_PREVENT_Y_PERIODICITY */
150    
151     CALL MPI_CART_CREATE(
152 adcroft 1.8 I MPI_COMM_MODEL,2,mpiGridSpec,mpiPeriodicity,_mpiTRUE_,
153 cnh 1.1 O mpiComm, mpiRC )
154     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
155     eeBootError = .TRUE.
156 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
157 cnh 1.1 & 'S/R INI_PROCS: MPI_CART_CREATE return code',
158     & mpiRC
159     CALL PRINT_ERROR( msgBuffer , myThid)
160     GOTO 999
161     ENDIF
162    
163     C-- Get my location on the grid
164     CALL MPI_CART_COORDS( mpiComm, mpiMyId, 2, mpiGridSpec, mpiRC )
165     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
166     eeBootError = .TRUE.
167 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
168 cnh 1.1 & 'S/R INI_PROCS: MPI_CART_COORDS return code',
169     & mpiRC
170     CALL PRINT_ERROR( msgBuffer , myThid)
171     GOTO 999
172     ENDIF
173 cnh 1.6 myPid = mpiMyId
174 cnh 1.1 mpiPx = mpiGridSpec(1)
175     mpiPy = mpiGridSpec(2)
176     mpiXGlobalLo = 1 + sNx*nSx*(mpiPx)
177     mpiYGlobalLo = 1 + sNy*nSy*(mpiPy)
178     myXGlobalLo = mpiXGlobalLo
179     myYGlobalLo = mpiYGlobalLo
180 dimitri 1.15
181     C-- To speed-up mpi gather and scatter routines, myXGlobalLo
182     C and myYGlobalLo from each process are transferred to
183     C a common block array. This allows process 0 to know
184     C the location of the domains controlled by each process.
185 dimitri 1.19 mpiBufSize=1
186     mpiRequest=0
187 dimitri 1.15 DO npe = 0, numberOfProcs-1
188 adcroft 1.16 CALL MPI_ISEND (myXGlobalLo, mpiBufSize, MPI_INTEGER,
189     & npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
190 dimitri 1.15 ENDDO
191     DO npe = 0, numberOfProcs-1
192 adcroft 1.16 CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
193 dimitri 1.15 & npe, npe, MPI_COMM_MODEL, istatus, ierr)
194     mpi_myXGlobalLo(npe+1) = itemp
195     ENDDO
196     DO npe = 0, numberOfProcs-1
197 adcroft 1.16 CALL MPI_ISEND (myYGlobalLo, mpiBufSize, MPI_INTEGER,
198     & npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)
199 dimitri 1.15 ENDDO
200     DO npe = 0, numberOfProcs-1
201 adcroft 1.16 CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,
202 dimitri 1.15 & npe, npe, MPI_COMM_MODEL, istatus, ierr)
203     mpi_myYGlobalLo(npe+1) = itemp
204     ENDDO
205    
206 cnh 1.6 myPx = mpiPx+1
207     myPy = mpiPy+1
208 cnh 1.1 C-- Get MPI id for neighboring procs.
209     mpiGridSpec(1) = mpiPx-1
210 adcroft 1.9 IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
211     & .AND. mpiGridSpec(1) .LT. 0 )
212 cnh 1.1 & mpiGridSpec(1) = nPx-1
213     mpiGridSpec(2) = mpiPy
214     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
215     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
216     eeBootError = .TRUE.
217 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
218 cnh 1.1 & 'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',
219     & mpiRC
220     CALL PRINT_ERROR( msgBuffer , myThid)
221     GOTO 999
222     ENDIF
223     pidW = mpiPidW
224     mpiGridSpec(1) = mpiPx+1
225 adcroft 1.9 IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
226     & .AND. mpiGridSpec(1) .GT. nPx-1 )
227 cnh 1.1 & mpiGridSpec(1) = 0
228     mpiGridSpec(2) = mpiPy
229     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )
230     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
231     eeBootError = .TRUE.
232 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
233 cnh 1.1 & 'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',
234     & mpiRC
235     CALL PRINT_ERROR( msgBuffer , myThid)
236     GOTO 999
237     ENDIF
238     pidE = mpiPidE
239     mpiGridSpec(1) = mpiPx
240     mpiGridSpec(2) = mpiPy-1
241 adcroft 1.9 IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
242     & .AND. mpiGridSpec(2) .LT. 0 )
243 cnh 1.1 & mpiGridSpec(2) = nPy - 1
244     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidS , mpiRC )
245     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
246     eeBootError = .TRUE.
247 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
248 cnh 1.1 & 'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',
249     & mpiRC
250     CALL PRINT_ERROR( msgBuffer , myThid)
251     GOTO 999
252     ENDIF
253     pidS = mpiPidS
254     mpiGridSpec(1) = mpiPx
255     mpiGridSpec(2) = mpiPy+1
256 adcroft 1.9 IF ( mpiPeriodicity(2) .EQ. _mpiTRUE_
257     & .AND. mpiGridSpec(2) .GT. nPy-1 )
258 cnh 1.1 & mpiGridSpec(2) = 0
259     CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidN , mpiRC )
260     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
261     eeBootError = .TRUE.
262 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
263 cnh 1.1 & 'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',
264     & mpiRC
265     CALL PRINT_ERROR( msgBuffer , myThid)
266     GOTO 999
267     ENDIF
268     pidN = mpiPidN
269    
270     C-- Print summary of processor mapping on standard output
271     CALL MPI_GET_PROCESSOR_NAME( mpiProcNam, mpilProcNam, mpiRC )
272     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
273     eeBootError = .TRUE.
274 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
275 cnh 1.1 & 'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',
276     & mpiRC
277     CALL PRINT_ERROR( msgBuffer , myThid)
278     GOTO 999
279     ENDIF
280 adcroft 1.9 WRITE(msgBuffer,'(A)')
281     & '======= Starting MPI parallel Run ========='
282 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
283     & SQUEEZE_BOTH , myThid)
284     WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',
285     & mpiProcNam(1:mpilProcNam)
286     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
287     & SQUEEZE_RIGHT , myThid)
288     WRITE(msgBuffer,'(A,I3,A,I3,A,I3,A,I3,A)') ' Located at (',
289     & mpiPx,',',mpiPy,
290     & ') on processor grid (0:',nPx-1,',0:',nPy-1,')'
291     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
292     & SQUEEZE_RIGHT , myThid)
293     WRITE(msgBuffer,'(A,I4,A,I4,A,I4,A,I4,A)') ' Origin at (',
294     & mpiXGlobalLo,',',mpiYGLobalLo,
295     & ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'
296     CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
297     & SQUEEZE_RIGHT , myThid)
298 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
299     & ' North neighbor = processor ', mpiPidN
300 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
301     & SQUEEZE_RIGHT , myThid)
302 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
303     & ' South neighbor = processor ', mpiPidS
304 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
305     & SQUEEZE_RIGHT , myThid)
306 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
307     & ' East neighbor = processor ', mpiPidE
308 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
309     & SQUEEZE_RIGHT , myThid)
310 adcroft 1.9 WRITE(msgBuffer,'(A,I4.4)')
311     & ' West neighbor = processor ', mpiPidW
312 cnh 1.1 CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
313     & SQUEEZE_RIGHT , myThid)
314     C
315     C-- Create MPI types for transfer of array edges.
316     C-- Four and eight byte primitive (one block only) datatypes.
317     C-- These are common to all threads in the process.
318     C Notes:
319     C ======
320     C 1. The datatypes MPI_REAL4 and MPI_REAL8 are usually predefined.
321     C If they are not defined code must be added to create them -
322     C the MPI standard leaves optional whether they exist.
323     C 2. Per thread datatypes that handle all the edges for a thread
324     C are defined based on the type defined here.
325     C--
326     C-- xFace datatypes (east<-->west messages)
327     C--
328     C xFace (y=constant) for XY arrays with real*4 declaration.
329     arrElSep = (sNx+OLx*2)
330     elCount = sNy+OLy*2
331     elLen = OLx
332     elStride = arrElSep
333 ce107 1.22 #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
334 adcroft 1.13 CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL,
335     & mpiTypeXFaceBlock_xy_r4, mpiRC)
336     #else
337 cnh 1.1 CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL4,
338     & mpiTypeXFaceBlock_xy_r4, mpiRC)
339 adcroft 1.13 #endif
340 cnh 1.1 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
341     eeBootError = .TRUE.
342 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
343 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
344 cnh 1.1 & mpiRC
345     CALL PRINT_ERROR( msgBuffer , myThid)
346     ENDIF
347     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)
348     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
349     eeBootError = .TRUE.
350 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
351 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
352 cnh 1.1 & mpiRC
353     CALL PRINT_ERROR( msgBuffer , myThid)
354     ENDIF
355    
356     C xFace (y=constant) for XY arrays with real*8 declaration.
357 ce107 1.22 #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
358 adcroft 1.13 CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_DOUBLE_PRECISION,
359     & mpiTypeXFaceBlock_xy_r8, mpiRC)
360     #else
361 cnh 1.1 CALL MPI_TYPE_VECTOR(elCount,elLen,elStride,MPI_REAL8,
362     & mpiTypeXFaceBlock_xy_r8, mpiRC)
363 adcroft 1.13 #endif
364 cnh 1.1 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
365     eeBootError = .TRUE.
366 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
367 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
368 cnh 1.1 & mpiRC
369     CALL PRINT_ERROR( msgBuffer , myThid)
370     ENDIF
371     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)
372     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
373     eeBootError = .TRUE.
374 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
375 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
376 cnh 1.1 & mpiRC
377     CALL PRINT_ERROR( msgBuffer , myThid)
378     ENDIF
379    
380     C xFace (y=constant) for XYZ arrays with real*4 declaration.
381     arrElSize = 4
382     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)
383 cnh 1.5 elCount = Nr
384 cnh 1.1 elLen = 1
385     elStride = arrElSize*arrElSep
386     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
387     & mpiTypeXFaceBlock_xy_r4,
388     & mpiTypeXFaceBlock_xyz_r4, mpiRC)
389     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
390     eeBootError = .TRUE.
391 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
392 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
393 cnh 1.1 & mpiRC
394     CALL PRINT_ERROR( msgBuffer , myThid)
395     ENDIF
396     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)
397     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
398     eeBootError = .TRUE.
399 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
400 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r4)',
401 cnh 1.1 & mpiRC
402     CALL PRINT_ERROR( msgBuffer , myThid)
403     ENDIF
404    
405     C xFace (y=constant) for XYZ arrays with real*8 declaration.
406     arrElSize = 8
407     elStride = arrElSize*arrElSep
408     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
409     & mpiTypeXFaceBlock_xy_r8,
410     & mpiTypeXFaceBlock_xyz_r8, mpiRC)
411     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
412     eeBootError = .TRUE.
413 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
414 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
415 cnh 1.1 & mpiRC
416     CALL PRINT_ERROR( msgBuffer , myThid)
417     ENDIF
418     CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)
419     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
420     eeBootError = .TRUE.
421 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
422 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
423 cnh 1.1 & mpiRC
424     CALL PRINT_ERROR( msgBuffer , myThid)
425     ENDIF
426     C--
427     C-- yFace datatypes (north<-->south messages)
428     C--
429     C yFace (x=constant) for XY arrays with real*4 declaration
430     elCount = OLy*(sNx+OLx*2)
431 ce107 1.22 #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
432 adcroft 1.13 CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL,
433     & mpiTypeYFaceBlock_xy_r4, mpiRC)
434     #else
435 cnh 1.1 CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL4,
436     & mpiTypeYFaceBlock_xy_r4, mpiRC)
437 adcroft 1.13 #endif
438 cnh 1.1 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
439     eeBootError = .TRUE.
440 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
441 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
442 cnh 1.1 & mpiRC
443     CALL PRINT_ERROR( msgBuffer , myThid)
444     ENDIF
445     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)
446     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
447     eeBootError = .TRUE.
448 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
449 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
450 cnh 1.1 & mpiRC
451     CALL PRINT_ERROR( msgBuffer , myThid)
452     ENDIF
453     C yFace (x=constant) for XY arrays with real*8 declaration
454 ce107 1.22 #if (defined (TARGET_SGI) || defined (TARGET_AIX) || defined(TARGET_LAM))
455 adcroft 1.13 CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_DOUBLE_PRECISION,
456     & mpiTypeYFaceBlock_xy_r8, mpiRC)
457     #else
458 cnh 1.1 CALL MPI_TYPE_CONTIGUOUS(elCount,MPI_REAL8,
459     & mpiTypeYFaceBlock_xy_r8, mpiRC)
460 adcroft 1.13 #endif
461 cnh 1.1 IF ( mpiRC .NE. MPI_SUCCESS ) THEN
462     eeBootError = .TRUE.
463 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
464 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
465 cnh 1.1 & mpiRC
466     CALL PRINT_ERROR( msgBuffer , myThid)
467     ENDIF
468     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)
469     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
470     eeBootError = .TRUE.
471 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
472 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
473 cnh 1.1 & mpiRC
474     CALL PRINT_ERROR( msgBuffer , myThid)
475     ENDIF
476     C yFace (x=constant) for XYZ arrays with real*4 declaration
477     arrElSize = 4
478     arrElSep = (sNx+OLx*2)*(sNy+OLy*2)
479 cnh 1.5 elCount = Nr
480 cnh 1.1 elLen = 1
481     elStride = arrElSize*arrElSep
482     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
483     & mpiTypeYFaceBlock_xy_r4,
484     & mpiTypeYFaceBlock_xyz_r4, mpiRC)
485     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
486     eeBootError = .TRUE.
487 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
488 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
489 cnh 1.1 & mpiRC
490     CALL PRINT_ERROR( msgBuffer , myThid)
491     ENDIF
492     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)
493     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
494     eeBootError = .TRUE.
495 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
496 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
497 cnh 1.1 & mpiRC
498     CALL PRINT_ERROR( msgBuffer , myThid)
499     ENDIF
500     C yFace (x=constant) for XYZ arrays with real*8 declaration
501     arrElSize = 8
502     elStride = arrElSize*arrElSep
503     CALL MPI_TYPE_HVECTOR(elCount,elLen,elStride,
504     & mpiTypeYFaceBlock_xy_r8,
505     & mpiTypeYFaceBlock_xyz_r8, mpiRC)
506     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
507     eeBootError = .TRUE.
508 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
509 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
510 cnh 1.1 & mpiRC
511     CALL PRINT_ERROR( msgBuffer , myThid)
512     ENDIF
513     CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)
514     IF ( mpiRC .NE. MPI_SUCCESS ) THEN
515     eeBootError = .TRUE.
516 adcroft 1.11 WRITE(msgBuffer,'(A,I5)')
517 adcroft 1.9 & 'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
518 cnh 1.1 & mpiRC
519     CALL PRINT_ERROR( msgBuffer , myThid)
520     ENDIF
521    
522     C-- Assign MPI values used in generating unique tags for messages.
523     mpiTagW = 1
524     mpiTagE = 2
525     mpiTagS = 3
526     mpiTagN = 4
527    
528     C
529 adcroft 1.8 CALL MPI_Barrier(MPI_COMM_MODEL,mpiRC)
530 cnh 1.1
531    
532     C
533     #ifndef ALWAYS_USE_MPI
534     ENDIF
535     #endif
536     #endif /* ALLOW_USE_MPI */
537    
538     999 CONTINUE
539    
540     RETURN
541     END
542 cnh 1.6
543 jmc 1.23 C $Id: ini_procs.F,v 1.22 2005/02/18 19:43:27 ce107 Exp $

  ViewVC Help
Powered by ViewVC 1.1.22