/[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.23 by jmc, Sat Nov 5 00:51:06 2005 UTC revision 1.26 by dfer, Wed May 6 02:44:45 2009 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          INTEGER  IFNBLNK, ILNBLNK
34          EXTERNAL IFNBLNK
35          EXTERNAL ILNBLNK
36    
37  C     !LOCAL VARIABLES:  C     !LOCAL VARIABLES:
38  C     === Local variables ===  C     === Local variables ===
 #ifdef ALLOW_USE_MPI  
39  C     msgBuffer        :: IO buffer  C     msgBuffer        :: IO buffer
40  C     myThid           :: Dummy thread id  C     myThid           :: Dummy thread id
41  C     mpiRC            :: Error code reporting variable used  C     mpiRC            :: Error code reporting variable used
42  C                         with MPI.  C                         with MPI.
43  C     mpiGridSpec      :: No. of processes in X and Y.  C     mpiGridSpec      :: No. of processes in X and Y.
44  C     mpiPeriodicity   :: Flag indicating XY priodicity to MPI.  C     mpiPeriodicity   :: Flag indicating XY priodicity to MPI.
# Line 55  C                         units. Line 60  C                         units.
60        INTEGER mpiPeriodicity(2)        INTEGER mpiPeriodicity(2)
61        INTEGER mpiLProcNam        INTEGER mpiLProcNam
62        CHARACTER*(MPI_MAX_PROCESSOR_NAME) mpiProcNam        CHARACTER*(MPI_MAX_PROCESSOR_NAME) mpiProcNam
63          INTEGER i1, i2
64        INTEGER arrElSize        INTEGER arrElSize
65        INTEGER arrElSep        INTEGER arrElSep
66        INTEGER elCount        INTEGER elCount
67        INTEGER elLen        INTEGER elLen
68        INTEGER elStride        INTEGER elStride
69        INTEGER npe,itemp,ierr,istatus(MPI_STATUS_SIZE)        INTEGER npe,itemp(2),ierr,istatus(MPI_STATUS_SIZE)
70        INTEGER mpiBufSize,mpiRequest        INTEGER mpiBufSize,mpiRequest
71  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
72        INTEGER myThid        INTEGER myThid
# Line 155  C      Could be periodic in X and/or Y - Line 161  C      Could be periodic in X and/or Y -
161          eeBootError = .TRUE.          eeBootError = .TRUE.
162          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
163       &        'S/R INI_PROCS: MPI_CART_CREATE return code',       &        'S/R INI_PROCS: MPI_CART_CREATE return code',
164       &        mpiRC       &        mpiRC
165          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
166          GOTO 999          GOTO 999
167         ENDIF         ENDIF
# Line 166  C--    Get my location on the grid Line 172  C--    Get my location on the grid
172          eeBootError = .TRUE.          eeBootError = .TRUE.
173          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
174       &        'S/R INI_PROCS: MPI_CART_COORDS return code',       &        'S/R INI_PROCS: MPI_CART_COORDS return code',
175       &        mpiRC       &        mpiRC
176          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
177          GOTO 999          GOTO 999
178         ENDIF         ENDIF
# Line 182  C--   To speed-up mpi gather and scatter Line 188  C--   To speed-up mpi gather and scatter
188  C     and myYGlobalLo from each process are transferred to  C     and myYGlobalLo from each process are transferred to
189  C     a common block array.  This allows process 0 to know  C     a common block array.  This allows process 0 to know
190  C     the location of the domains controlled by each process.  C     the location of the domains controlled by each process.
        mpiBufSize=1  
        mpiRequest=0  
        DO npe = 0, numberOfProcs-1  
           CALL MPI_ISEND (myXGlobalLo, mpiBufSize, MPI_INTEGER,  
      &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)  
        ENDDO  
191         DO npe = 0, numberOfProcs-1         DO npe = 0, numberOfProcs-1
192            CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,            itemp(1) = myXGlobalLo
193       &         npe, npe, MPI_COMM_MODEL, istatus, ierr)            itemp(2) = myYGlobalLo
194            mpi_myXGlobalLo(npe+1) = itemp            CALL MPI_BCAST(itemp, 2, MPI_INTEGER, npe,
195         ENDDO       &         MPI_COMM_MODEL, ierr)
196         DO npe = 0, numberOfProcs-1            mpi_myXGlobalLo(npe+1) = itemp(1)
197            CALL MPI_ISEND (myYGlobalLo, mpiBufSize, MPI_INTEGER,            mpi_myYGlobalLo(npe+1) = itemp(2)
      &         npe, mpiMyId, MPI_COMM_MODEL, mpiRequest, ierr)  
        ENDDO  
        DO npe = 0, numberOfProcs-1  
           CALL MPI_RECV (itemp, mpiBufSize, MPI_INTEGER,  
      &         npe, npe, MPI_COMM_MODEL, istatus, ierr)  
           mpi_myYGlobalLo(npe+1) = itemp  
198         ENDDO         ENDDO
199    
200         myPx = mpiPx+1         myPx = mpiPx+1
# Line 208  C     the location of the domains contro Line 202  C     the location of the domains contro
202  C--    Get MPI id for neighboring procs.  C--    Get MPI id for neighboring procs.
203         mpiGridSpec(1) = mpiPx-1         mpiGridSpec(1) = mpiPx-1
204         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_         IF ( mpiPeriodicity(1) .EQ. _mpiTRUE_
205       &   .AND. mpiGridSpec(1) .LT. 0 )       &   .AND. mpiGridSpec(1) .LT. 0 )
206       &  mpiGridSpec(1) = nPx-1       &  mpiGridSpec(1) = nPx-1
207         mpiGridSpec(2) = mpiPy         mpiGridSpec(2) = mpiPy
208         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )         CALL MPI_CART_RANK( mpiComm, mpiGridSpec, mpiPidW , mpiRC )
# Line 216  C--    Get MPI id for neighboring procs. Line 210  C--    Get MPI id for neighboring procs.
210          eeBootError = .TRUE.          eeBootError = .TRUE.
211          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
212       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidW) return code',
213       &        mpiRC       &        mpiRC
214          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
215          GOTO 999          GOTO 999
216         ENDIF         ENDIF
# Line 231  C--    Get MPI id for neighboring procs. Line 225  C--    Get MPI id for neighboring procs.
225          eeBootError = .TRUE.          eeBootError = .TRUE.
226          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
227       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidE) return code',
228       &        mpiRC       &        mpiRC
229          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
230          GOTO 999          GOTO 999
231         ENDIF         ENDIF
# Line 246  C--    Get MPI id for neighboring procs. Line 240  C--    Get MPI id for neighboring procs.
240          eeBootError = .TRUE.          eeBootError = .TRUE.
241          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
242       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidS) 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 261  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 (pidN) return code',       &        'S/R INI_PROCS: MPI_CART_RANK (pidN) 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 273  C--    Print summary of processor mappin Line 267  C--    Print summary of processor mappin
267          eeBootError = .TRUE.          eeBootError = .TRUE.
268          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
269       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',       &        'S/R INI_PROCS: MPI_GET_PROCESSOR_NAME return code',
270       &        mpiRC       &        mpiRC
271          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
272          GOTO 999          GOTO 999
273         ENDIF         ENDIF
274         WRITE(msgBuffer,'(A)')         WRITE(msgBuffer,'(A)')
275       &   '======= Starting MPI parallel Run ========='       &   '======= Starting MPI parallel Run ========='
276         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
277       &  SQUEEZE_BOTH , myThid)       &  SQUEEZE_BOTH , myThid)
278         WRITE(msgBuffer,'(A,A64)') ' My Processor Name = ',         i1 = IFNBLNK(mpiProcNam)
279       &  mpiProcNam(1:mpilProcNam)         i2 = ILNBLNK(mpiProcNam)
280         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         WRITE(msgBuffer,'(A,I3,A,A)') ' My Processor Name (len:',
281         &  mpilProcNam, ' ) = ', mpiProcNam(i1:mpilProcNam)
282           CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
283       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
284         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 (',
285       &  mpiPx,',',mpiPy,       &  mpiPx,',',mpiPy,
286       &  ') on processor grid (0:',nPx-1,',0:',nPy-1,')'       &  ') on processor grid (0:',nPx-1,',0:',nPy-1,')'
287         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
288       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
289         WRITE(msgBuffer,'(A,I4,A,I4,A,I4,A,I4,A)') ' Origin at  (',         WRITE(msgBuffer,'(A,I4,A,I4,A,I4,A,I4,A)') ' Origin at  (',
290       &  mpiXGlobalLo,',',mpiYGLobalLo,       &  mpiXGlobalLo,',',mpiYGLobalLo,
291       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'       &  ') on global grid (1:',nPx*sNx*nSx,',1:',nPy*sNy*nSy,')'
292         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
293       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
294         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
295       &   ' North neighbor = processor ', mpiPidN       &   ' North neighbor = processor ', mpiPidN
296         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
297       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
298         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
299       &   ' South neighbor = processor ', mpiPidS       &   ' South neighbor = processor ', mpiPidS
300         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
301       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
302         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
303       &   '  East neighbor = processor ', mpiPidE       &   '  East neighbor = processor ', mpiPidE
304         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
305       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
306         WRITE(msgBuffer,'(A,I4.4)')         WRITE(msgBuffer,'(A,I4.4)')
307       &   '  West neighbor = processor ', mpiPidW       &   '  West neighbor = processor ', mpiPidW
308         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,         CALL PRINT_MESSAGE( msgBuffer, standardMessageUnit,
309       &  SQUEEZE_RIGHT , myThid)       &  SQUEEZE_RIGHT , myThid)
310  C  C
311  C--    Create MPI types for transfer of array edges.  C--    Create MPI types for transfer of array edges.
# Line 341  C      xFace (y=constant) for XY arrays Line 337  C      xFace (y=constant) for XY arrays
337          eeBootError = .TRUE.          eeBootError = .TRUE.
338          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
339       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r4)',
340       &        mpiRC       &        mpiRC
341          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
342         ENDIF         ENDIF
343         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r4, mpiRC)
# Line 349  C      xFace (y=constant) for XY arrays Line 345  C      xFace (y=constant) for XY arrays
345          eeBootError = .TRUE.          eeBootError = .TRUE.
346          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
347       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r4)',
348       &        mpiRC       &        mpiRC
349          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
350         ENDIF         ENDIF
351    
# Line 365  C      xFace (y=constant) for XY arrays Line 361  C      xFace (y=constant) for XY arrays
361          eeBootError = .TRUE.          eeBootError = .TRUE.
362          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
363       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_VECTOR (mpiTypeXFaceBlock_xy_r8)',
364       &        mpiRC       &        mpiRC
365          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
366         ENDIF         ENDIF
367         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xy_r8, mpiRC)
# Line 373  C      xFace (y=constant) for XY arrays Line 369  C      xFace (y=constant) for XY arrays
369          eeBootError = .TRUE.          eeBootError = .TRUE.
370          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
371       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xy_r8)',
372       &        mpiRC       &        mpiRC
373          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
374         ENDIF         ENDIF
375    
# Line 390  C      xFace (y=constant) for XYZ arrays Line 386  C      xFace (y=constant) for XYZ arrays
386          eeBootError = .TRUE.          eeBootError = .TRUE.
387          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
388       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r4)',
389       &        mpiRC       &        mpiRC
390          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
391         ENDIF         ENDIF
392         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r4, mpiRC)
# Line 398  C      xFace (y=constant) for XYZ arrays Line 394  C      xFace (y=constant) for XYZ arrays
394          eeBootError = .TRUE.          eeBootError = .TRUE.
395          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
396       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT  (mpiTypeXFaceBlock_xyz_r4)',
397       &        mpiRC       &        mpiRC
398          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
399         ENDIF         ENDIF
400    
# Line 412  C      xFace (y=constant) for XYZ arrays Line 408  C      xFace (y=constant) for XYZ arrays
408          eeBootError = .TRUE.          eeBootError = .TRUE.
409          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
410       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeXFaceBlock_xyz_r8)',
411       &        mpiRC       &        mpiRC
412          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
413         ENDIF         ENDIF
414         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeXFaceBlock_xyz_r8, mpiRC)
# Line 420  C      xFace (y=constant) for XYZ arrays Line 416  C      xFace (y=constant) for XYZ arrays
416          eeBootError = .TRUE.          eeBootError = .TRUE.
417          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
418       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeXFaceBlock_xyz_r8)',
419       &        mpiRC       &        mpiRC
420          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
421         ENDIF         ENDIF
422  C--  C--
# Line 439  C      yFace (x=constant) for XY arrays Line 435  C      yFace (x=constant) for XY arrays
435          eeBootError = .TRUE.          eeBootError = .TRUE.
436          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
437       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r4)',
438       &        mpiRC       &        mpiRC
439          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
440         ENDIF         ENDIF
441         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r4, mpiRC)
# Line 447  C      yFace (x=constant) for XY arrays Line 443  C      yFace (x=constant) for XY arrays
443          eeBootError = .TRUE.          eeBootError = .TRUE.
444          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
445       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r4)',
446       &        mpiRC       &        mpiRC
447          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
448         ENDIF         ENDIF
449  C      yFace (x=constant) for XY arrays with real*8 declaration  C      yFace (x=constant) for XY arrays with real*8 declaration
# Line 462  C      yFace (x=constant) for XY arrays Line 458  C      yFace (x=constant) for XY arrays
458          eeBootError = .TRUE.          eeBootError = .TRUE.
459          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
460       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_CONTIGUOUS (mpiTypeYFaceBlock_xy_r8)',
461       &        mpiRC       &        mpiRC
462          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
463         ENDIF         ENDIF
464         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xy_r8, mpiRC)
# Line 470  C      yFace (x=constant) for XY arrays Line 466  C      yFace (x=constant) for XY arrays
466          eeBootError = .TRUE.          eeBootError = .TRUE.
467          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
468       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xy_r8)',
469       &        mpiRC       &        mpiRC
470          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
471         ENDIF         ENDIF
472  C      yFace (x=constant) for XYZ arrays with real*4 declaration  C      yFace (x=constant) for XYZ arrays with real*4 declaration
# Line 486  C      yFace (x=constant) for XYZ arrays Line 482  C      yFace (x=constant) for XYZ arrays
482          eeBootError = .TRUE.          eeBootError = .TRUE.
483          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
484       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r4)',
485       &        mpiRC       &        mpiRC
486          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
487         ENDIF         ENDIF
488         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r4, mpiRC)
# Line 494  C      yFace (x=constant) for XYZ arrays Line 490  C      yFace (x=constant) for XYZ arrays
490          eeBootError = .TRUE.          eeBootError = .TRUE.
491          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
492       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r4)',
493       &        mpiRC       &        mpiRC
494          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
495         ENDIF         ENDIF
496  C      yFace (x=constant) for XYZ arrays with real*8 declaration  C      yFace (x=constant) for XYZ arrays with real*8 declaration
# Line 507  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_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_HVECTOR (mpiTypeYFaceBlock_xyz_r8)',
506       &        mpiRC       &        mpiRC
507          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
508         ENDIF         ENDIF
509         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)         CALL MPI_TYPE_COMMIT( mpiTypeYFaceBlock_xyz_r8, mpiRC)
# Line 515  C      yFace (x=constant) for XYZ arrays Line 511  C      yFace (x=constant) for XYZ arrays
511          eeBootError = .TRUE.          eeBootError = .TRUE.
512          WRITE(msgBuffer,'(A,I5)')          WRITE(msgBuffer,'(A,I5)')
513       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',       &   'S/R INI_PROCS: MPI_TYPE_COMMIT (mpiTypeYFaceBlock_xyz_r8)',
514       &        mpiRC       &        mpiRC
515          CALL PRINT_ERROR( msgBuffer , myThid)          CALL PRINT_ERROR( msgBuffer , myThid)
516         ENDIF         ENDIF
517    
# Line 539  C Line 535  C
535    
536        RETURN        RETURN
537        END        END
   
 C $Id$  

Legend:
Removed from v.1.23  
changed lines
  Added in v.1.26

  ViewVC Help
Powered by ViewVC 1.1.22