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

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

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

revision 1.24 by heimbach, Wed Apr 16 20:46:46 2008 UTC revision 1.29 by zhc, Tue Jul 6 23:12:51 2010 UTC
# Line 11  C     !INTERFACE: Line 11  C     !INTERFACE:
11    
12  C     !DESCRIPTION:  C     !DESCRIPTION:
13  C     *==========================================================*  C     *==========================================================*
14  C     | SUBROUTINE INI\_PROCS                                        C     | SUBROUTINE INI\_PROCS
15  C     | o Initialise multiple concurrent processes environment.    C     | o Initialise multiple concurrent processes environment.
16  C     *==========================================================*  C     *==========================================================*
17  C     | Under MPI this routine calls various MPI service routines  C     | Under MPI this routine calls various MPI service routines
18  C     | that map the model grid to MPI processes. The information  C     | that map the model grid to MPI processes. The information
19  C     | is then stored in a common block for later use.            C     | is then stored in a common block for later use.
20  C     | Note: This routine can also be compiled with CPP            C     | Note: This routine can also be compiled with CPP
21  C     | directives set so that no multi-processing is initialise.  C     | directives set so that no multi-processing is initialise.
22  C     | This is OK and should work fine.                            C     | This is OK and should work fine.
23  C     *==========================================================*  C     *==========================================================*
24    
25  C     !USES:  C     !USES:
# Line 28  C     === Global data === Line 28  C     === Global data ===
28  #include "EEPARAMS.h"  #include "EEPARAMS.h"
29  #include "EESUPPORT.h"  #include "EESUPPORT.h"
30    
31    #ifdef ALLOW_USE_MPI
32    C     !FUNCTIONS:
33    
34  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
35  C     === Local variables ===  C     === Local variables ===
 #ifdef ALLOW_USE_MPI  
36  C     msgBuffer        :: IO buffer  C     msgBuffer        :: IO buffer
37  C     myThid           :: Dummy thread id  C     myThid           :: Dummy thread id
38  C     mpiRC            :: Error code reporting variable used  C     mpiRC            :: Error code reporting variable used
39  C                         with MPI.  C                         with MPI.
40  C     mpiGridSpec      :: No. of processes in X and Y.  C     mpiGridSpec      :: No. of processes in X and Y.
41  C     mpiPeriodicity   :: Flag indicating XY priodicity to MPI.  C     mpiPeriodicity   :: Flag indicating XY priodicity to MPI.
# Line 155  C      Could be periodic in X and/or Y - Line 157  C      Could be periodic in X and/or Y -
157          eeBootError = .TRUE.          eeBootError = .TRUE.
158          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
159       &        'S/R INI_PROCS: MPI_CART_CREATE return code',       &        'S/R INI_PROCS: MPI_CART_CREATE return code',
160       &        mpiRC       &        mpiRC
161          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
162          GOTO 999          GOTO 999
163         ENDIF         ENDIF
# Line 166  C--    Get my location on the grid Line 168  C--    Get my location on the grid
168          eeBootError = .TRUE.          eeBootError = .TRUE.
169          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
170       &        'S/R INI_PROCS: MPI_CART_COORDS return code',       &        'S/R INI_PROCS: MPI_CART_COORDS return code',
171       &        mpiRC       &        mpiRC
172          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
173          GOTO 999          GOTO 999
174         ENDIF         ENDIF
# Line 185  C     the location of the domains contro Line 187  C     the location of the domains contro
187         DO npe = 0, numberOfProcs-1         DO npe = 0, numberOfProcs-1
188            itemp(1) = myXGlobalLo            itemp(1) = myXGlobalLo
189            itemp(2) = myYGlobalLo            itemp(2) = myYGlobalLo
190            CALL MPI_BCAST(itemp, 2, MPI_INTEGER, npe,            CALL MPI_BCAST(itemp, 2, MPI_INTEGER, npe,
191       &         MPI_COMM_MODEL, ierr)       &         MPI_COMM_MODEL, ierr)
192            mpi_myXGlobalLo(npe+1) = itemp(1)            mpi_myXGlobalLo(npe+1) = itemp(1)
193            mpi_myYGlobalLo(npe+1) = itemp(2)            mpi_myYGlobalLo(npe+1) = itemp(2)
# Line 196  C     the location of the domains contro Line 198  C     the location of the domains contro
198  C--    Get MPI id for neighboring procs.  C--    Get MPI id for neighboring procs.
199         mpiGridSpec(1) = mpiPx-1         mpiGridSpec(1) = mpiPx-1
200         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
201       &   .AND. mpiGridSpec(1) .LT. 0 )       &   .AND. mpiGridSpec(1) .LT. 0 )
202       &  mpiGridSpec(1) = nPx-1       &  mpiGridSpec(1) = nPx-1
203         mpiGridSpec(2) = mpiPy         mpiGridSpec(2) = mpiPy
204    
205    #ifdef ALLOW_NEST_CHILD
206          IF ( useNEST_CHILD) THEN
207           IF ( mpiPeriodicity(1) .EQ. _mpiFALSE_
208         &      .AND. mpiGridSpec(1) .LT. 0 )
209         &      mpiGridSpec(1) =  0
210          ENDIF
211    #endif /* ALLOW_NEST_CHILD */
212    
213    
214         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
215         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
216          eeBootError = .TRUE.          eeBootError = .TRUE.
217          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
218       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',
219       &        mpiRC       &        mpiRC
220          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
221          GOTO 999          GOTO 999
222         ENDIF         ENDIF
# Line 214  C--    Get MPI id for neighboring procs. Line 226  C--    Get MPI id for neighboring procs.
226       &   .AND. mpiGridSpec(1) .GT. nPx-1 )       &   .AND. mpiGridSpec(1) .GT. nPx-1 )
227       &  mpiGridSpec(1) = 0       &  mpiGridSpec(1) = 0
228         mpiGridSpec(2) = mpiPy         mpiGridSpec(2) = mpiPy
229    
230    #ifdef ALLOW_NEST_CHILD
231          IF ( useNEST_CHILD) THEN
232           IF ( mpiPeriodicity(1) .EQ. _mpiFALSE_
233         &   .AND. mpiGridSpec(1) .GT. nPx-1 )
234         &    mpiGridSpec(1) = nPx-1
235          ENDIF
236    #endif /* ALLOW_NEST_CHILD */
237    
238         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidE , mpiRC )
239         IF ( mpiRC .NE. MPI_SUCCESS ) THEN         IF ( mpiRC .NE. MPI_SUCCESS ) THEN
240          eeBootError = .TRUE.          eeBootError = .TRUE.
241          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
242       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',
243       &        mpiRC       &        mpiRC
244          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
245          GOTO 999          GOTO 999
246         ENDIF         ENDIF
# Line 234  C--    Get MPI id for neighboring procs. Line 255  C--    Get MPI id for neighboring procs.
255          eeBootError = .TRUE.          eeBootError = .TRUE.
256          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
257       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',
258       &        mpiRC       &        mpiRC
259          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
260          GOTO 999          GOTO 999
261         ENDIF         ENDIF
# Line 249  C--    Get MPI id for neighboring procs. Line 270  C--    Get MPI id for neighboring procs.
270          eeBootError = .TRUE.          eeBootError = .TRUE.
271          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
272       &        'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidN) return code',
273       &        mpiRC       &        mpiRC
274          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
275          GOTO 999          GOTO 999
276         ENDIF         ENDIF
# Line 261  C--    Print summary of processor mappin Line 282  C--    Print summary of processor mappin
282          eeBootError = .TRUE.          eeBootError = .TRUE.
283          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
284       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',
285       &        mpiRC       &        mpiRC
286          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
287          GOTO 999          GOTO 999
288         ENDIF         ENDIF
289         WRITE(msgBuffer,'(A)')         WRITE(msgBuffer,'(A)')
290       &   '======= Starting MPI parallel Run ========='       &   '======= Starting MPI parallel Run ========='
291         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
292       &  SQUEEZE_BOTH , myThid)       &  SQUEEZE_BOTH , myThid)
293         WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',         WRITE(msgBuffer,'(A,I3,A,A)') ' My Processor Name (len:',
294       &  mpiProcNam(1:mpilProcNam)       &  mpilProcNam, ' ) = ', mpiProcNam(1:mpilProcNam)
295         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
296       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
297         WRITE(msgBuffer,'(A,I3,A,I3,A,I3,A,I3,A)') ' Located at (',         WRITE(msgBuffer,'(A,I3,A,I3,A,I3,A,I3,A)') ' Located at (',
298       &  mpiPx,',',mpiPy,       &  mpiPx,',',mpiPy,
299       &  ') on processor grid (0:',nPx-1,',0:',nPy-1,')'       &  ') on processor grid (0:',nPx-1,',0:',nPy-1,')'
300         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
301       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
302         WRITE(msgBuffer,'(A,I4,A,I4,A,I4,A,I4,A)') ' Origin at  (',         WRITE(msgBuffer,'(A,I6,A,I6,A,I6,A,I6,A)') ' Origin at  (',
303       &  mpiXGlobalLo,',',mpiYGLobalLo,       &  mpiXGlobalLo,',',mpiYGLobalLo,
304       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'
305         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
306       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
307         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
308       &   ' North neighbor = processor ', mpiPidN       &   ' North neighbor = processor ', mpiPidN
309         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
310       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
311         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
312       &   ' South neighbor = processor ', mpiPidS       &   ' South neighbor = processor ', mpiPidS
313         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
314       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
315         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
316       &   '  East neighbor = processor ', mpiPidE       &   '  East neighbor = processor ', mpiPidE
317         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
318       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
319         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
320       &   '  West neighbor = processor ', mpiPidW       &   '  West neighbor = processor ', mpiPidW
321         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
322       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
323  C  C
324  C--    Create MPI types for transfer of array edges.  C--    Create MPI types for transfer of array edges.
# Line 329  C      xFace (y=constant) for XY arrays Line 350  C      xFace (y=constant) for XY arrays
350          eeBootError = .TRUE.          eeBootError = .TRUE.
351          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
352       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
353       &        mpiRC       &        mpiRC
354          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
355         ENDIF         ENDIF
356         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)
# Line 337  C      xFace (y=constant) for XY arrays Line 358  C      xFace (y=constant) for XY arrays
358          eeBootError = .TRUE.          eeBootError = .TRUE.
359          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
360       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
361       &        mpiRC       &        mpiRC
362          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
363         ENDIF         ENDIF
364    
# Line 353  C      xFace (y=constant) for XY arrays Line 374  C      xFace (y=constant) for XY arrays
374          eeBootError = .TRUE.          eeBootError = .TRUE.
375          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
376       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
377       &        mpiRC       &        mpiRC
378          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
379         ENDIF         ENDIF
380         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)
# Line 361  C      xFace (y=constant) for XY arrays Line 382  C      xFace (y=constant) for XY arrays
382          eeBootError = .TRUE.          eeBootError = .TRUE.
383          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
384       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
385       &        mpiRC       &        mpiRC
386          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
387         ENDIF         ENDIF
388    
# Line 378  C      xFace (y=constant) for XYZ arrays Line 399  C      xFace (y=constant) for XYZ arrays
399          eeBootError = .TRUE.          eeBootError = .TRUE.
400          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
401       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
402       &        mpiRC       &        mpiRC
403          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
404         ENDIF         ENDIF
405         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)
# Line 386  C      xFace (y=constant) for XYZ arrays Line 407  C      xFace (y=constant) for XYZ arrays
407          eeBootError = .TRUE.          eeBootError = .TRUE.
408          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
409       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',
410       &        mpiRC       &        mpiRC
411          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
412         ENDIF         ENDIF
413    
# Line 400  C      xFace (y=constant) for XYZ arrays Line 421  C      xFace (y=constant) for XYZ arrays
421          eeBootError = .TRUE.          eeBootError = .TRUE.
422          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
423       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
424       &        mpiRC       &        mpiRC
425          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
426         ENDIF         ENDIF
427         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)
# Line 408  C      xFace (y=constant) for XYZ arrays Line 429  C      xFace (y=constant) for XYZ arrays
429          eeBootError = .TRUE.          eeBootError = .TRUE.
430          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
431       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
432       &        mpiRC       &        mpiRC
433          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
434         ENDIF         ENDIF
435  C--  C--
# Line 427  C      yFace (x=constant) for XY arrays Line 448  C      yFace (x=constant) for XY arrays
448          eeBootError = .TRUE.          eeBootError = .TRUE.
449          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
450       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
451       &        mpiRC       &        mpiRC
452          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
453         ENDIF         ENDIF
454         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)
# Line 435  C      yFace (x=constant) for XY arrays Line 456  C      yFace (x=constant) for XY arrays
456          eeBootError = .TRUE.          eeBootError = .TRUE.
457          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
458       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
459       &        mpiRC       &        mpiRC
460          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
461         ENDIF         ENDIF
462  C      yFace (x=constant) for XY arrays with real*8 declaration  C      yFace (x=constant) for XY arrays with real*8 declaration
# Line 450  C      yFace (x=constant) for XY arrays Line 471  C      yFace (x=constant) for XY arrays
471          eeBootError = .TRUE.          eeBootError = .TRUE.
472          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
473       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
474       &        mpiRC       &        mpiRC
475          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
476         ENDIF         ENDIF
477         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)
# Line 458  C      yFace (x=constant) for XY arrays Line 479  C      yFace (x=constant) for XY arrays
479          eeBootError = .TRUE.          eeBootError = .TRUE.
480          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
481       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
482       &        mpiRC       &        mpiRC
483          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
484         ENDIF         ENDIF
485  C      yFace (x=constant) for XYZ arrays with real*4 declaration  C      yFace (x=constant) for XYZ arrays with real*4 declaration
# Line 474  C      yFace (x=constant) for XYZ arrays Line 495  C      yFace (x=constant) for XYZ arrays
495          eeBootError = .TRUE.          eeBootError = .TRUE.
496          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
497       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
498       &        mpiRC       &        mpiRC
499          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
500         ENDIF         ENDIF
501         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)
# Line 482  C      yFace (x=constant) for XYZ arrays Line 503  C      yFace (x=constant) for XYZ arrays
503          eeBootError = .TRUE.          eeBootError = .TRUE.
504          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
505       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
506       &        mpiRC       &        mpiRC
507          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
508         ENDIF         ENDIF
509  C      yFace (x=constant) for XYZ arrays with real*8 declaration  C      yFace (x=constant) for XYZ arrays with real*8 declaration
# Line 495  C      yFace (x=constant) for XYZ arrays Line 516  C      yFace (x=constant) for XYZ arrays
516          eeBootError = .TRUE.          eeBootError = .TRUE.
517          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
518       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
519       &        mpiRC       &        mpiRC
520          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
521         ENDIF         ENDIF
522         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)
# Line 503  C      yFace (x=constant) for XYZ arrays Line 524  C      yFace (x=constant) for XYZ arrays
524          eeBootError = .TRUE.          eeBootError = .TRUE.
525          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
526       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
527       &        mpiRC       &        mpiRC
528          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
529         ENDIF         ENDIF
530    
# Line 527  C Line 548  C
548    
549        RETURN        RETURN
550        END        END
   
 C $Id$  

Legend:
Removed from v.1.24  
changed lines
  Added in v.1.29

  ViewVC Help
Powered by ViewVC 1.1.22