/[MITgcm]/MITgcm/pkg/mdsio/mdsio_gl.F
ViewVC logotype

Diff of /MITgcm/pkg/mdsio/mdsio_gl.F

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

revision 1.16 by jahn, Tue Dec 30 00:14:05 2008 UTC revision 1.17 by jmc, Tue Jan 5 02:55:14 2010 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "MDSIO_OPTIONS.h"  #include "MDSIO_OPTIONS.h"
5    
6  C The five "public" routines supplied here are:  C--  File mdsio_gl.F: Routines to handle mid-level I/O interface.
7  C  C--   Contents
8  C MDSREADFIELD   - read model field from direct access global or tiled MDS file  C--   o MDSREADFIELD_3D_GL
9  C MDSWRITEFIELD  - write model field to direct access global or tiled MDS file  C--   o MDSWRITEFIELD_3D_GL
10  C MDSFINDUNIT    - returns an available (unused) I/O channel  C--   o MDSREADFIELD_2D_GL
11  C MDSREADVECTOR  - read vector from direct access global or tiled MDS file  C--   o MDSWRITEFIELD_2D_GL
12  C MDSWRITEVECTOR - write vector to direct access global or tiled MDS file  
13  C  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
 C all other routines are "private" to these utilities and ought  
 C not be accessed directly from the main code.  
 C  
 C Created:  03/16/99 adcroft@mit.edu  
 C Modified: 03/23/99 adcroft@mit.edu  
 C           To work with multiple records  
 C Modified: 03/29/99 eckert@mit.edu  
 C           Added arbitrary vector capability  
 C Modified: 07/27/99 eckert@mit.edu  
 C           Customized for state estimation (--> active_file_control.F)  
 C           this relates only to *mdsreadvector* and *mdswritevector*  
 C Modified: 07/28/99 eckert@mit.edu  
 C           inserted calls to *print_message* and *print_error*  
 C  
 C To be modified to work with MITgcmuv message routines.  
14    
 C=======================================================================  
15        SUBROUTINE MDSREADFIELD_3D_GL(        SUBROUTINE MDSREADFIELD_3D_GL(
16       I   fName,       I   fName,
17       I   filePrec,       I   filePrec,
# Line 68  C Created: 03/16/99 adcroft@mit.edu Line 52  C Created: 03/16/99 adcroft@mit.edu
52  C Global variables / common blocks  C Global variables / common blocks
53  #include "SIZE.h"  #include "SIZE.h"
54  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "EESUPPORT.h"  
55  #include "PARAMS.h"  #include "PARAMS.h"
56    
57  C Routine arguments  C Routine arguments
# Line 147  C Assign a free unit number as the I/O c Line 130  C Assign a free unit number as the I/O c
130        if ( useSingleCPUIO ) then        if ( useSingleCPUIO ) then
131    
132  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
133          IF( mpiMyId .EQ. 0 ) THEN          IF( myProcId .EQ. 0 ) THEN
134  #else  #else
135          IF ( .TRUE. ) THEN          IF ( .TRUE. ) THEN
136  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
# Line 171  C Otherwise stop program. Line 154  C Otherwise stop program.
154            open( dUnit, file=dataFName, status='old',            open( dUnit, file=dataFName, status='old',
155       &         access='direct', recl=length_of_rec )       &         access='direct', recl=length_of_rec )
156           else           else
157            write(msgbuf,'(2a)')            write(msgbuf,'(2a)')
158       &      ' MDSREADFIELD: filename: ',dataFName(1:IL)       &      ' MDSREADFIELD: filename: ',dataFName(1:IL)
159            call print_message( msgbuf, standardmessageunit,            call print_message( msgbuf, standardmessageunit,
160       &                        SQUEEZE_RIGHT , mythid)       &                        SQUEEZE_RIGHT , mythid)
# Line 228  C If we are reading from a global file t Line 211  C If we are reading from a global file t
211         fileIsOpen=.TRUE.         fileIsOpen=.TRUE.
212        endif        endif
213    
214  C Loop over all processors      C Loop over all processors
215        do jp=1,nPy        do jp=1,nPy
216        do ip=1,nPx        do ip=1,nPx
217  C Loop over all tiles  C Loop over all tiles
# Line 354  c      else of if ( .not. ( globalFile . Line 337  c      else of if ( .not. ( globalFile .
337         DO k=1,nNz         DO k=1,nNz
338    
339  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
340           IF( mpiMyId .EQ. 0 ) THEN           IF( myProcId .EQ. 0 ) THEN
341  #else  #else
342           IF ( .TRUE. ) THEN           IF ( .TRUE. ) THEN
343  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
# Line 412  c      end of if ( .not. ( globalFile .a Line 395  c      end of if ( .not. ( globalFile .a
395    
396        _END_MASTER( myThid )        _END_MASTER( myThid )
397    
398    #else /* ALLOW_CTRL */
399          STOP 'ABNORMAL END: S/R MDSREADFIELD_3D_GL is empty'
400  #endif /* ALLOW_CTRL */  #endif /* ALLOW_CTRL */
401  C     ------------------------------------------------------------------  C     ------------------------------------------------------------------
402        return        RETURN
403        end        END
404  C=======================================================================  
405    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
406    
 C=======================================================================  
407        SUBROUTINE MDSWRITEFIELD_3D_GL(        SUBROUTINE MDSWRITEFIELD_3D_GL(
408       I   fName,       I   fName,
409       I   filePrec,       I   filePrec,
# Line 469  C          open(dUnit, ..., status='old' Line 454  C          open(dUnit, ..., status='old'
454  C Global variables / common blocks  C Global variables / common blocks
455  #include "SIZE.h"  #include "SIZE.h"
456  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "EESUPPORT.h"  
457  #include "PARAMS.h"  #include "PARAMS.h"
458    
459  C Routine arguments  C Routine arguments
# Line 496  C Local variables Line 480  C Local variables
480        Real*4 r4seg(sNx)        Real*4 r4seg(sNx)
481        Real*8 r8seg(sNx)        Real*8 r8seg(sNx)
482        _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy)        _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy)
483        integer dimList(3,3),ndims        INTEGER dimList(3,3), nDims, map2gl(2)
484          _RL dummyRL(1)
485          CHARACTER*8 blank8c
486        integer length_of_rec        integer length_of_rec
487        logical fileIsOpen        logical fileIsOpen
488        character*(max_len_mbuf) msgbuf        character*(max_len_mbuf) msgbuf
# Line 516  CMM( Line 502  CMM(
502        integer pIL        integer pIL
503  CMM)  CMM)
504    
505          DATA dummyRL(1) / 0. _d 0 /
506          DATA blank8c / '        ' /
507    
508  C     ------------------------------------------------------------------  C     ------------------------------------------------------------------
509    
510  C Only do I/O if I am the master thread  C Only do I/O if I am the master thread
# Line 558  C globalFile is too slow, then try using Line 547  C globalFile is too slow, then try using
547    
548  C Master thread of process 0, only, opens a global file  C Master thread of process 0, only, opens a global file
549         _BEGIN_MASTER( myThid )         _BEGIN_MASTER( myThid )
550          IF( mpiMyId .EQ. 0 ) THEN          IF( myProcId .EQ. 0 ) THEN
551           write(dataFname,'(2a)') fName(1:IL),'.data'           write(dataFname,'(2a)') fName(1:IL),'.data'
552           length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid)           length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid)
553           if (irecord .EQ. 1) then           if (irecord .EQ. 1) then
# Line 573  C Master thread of process 0, only, open Line 562  C Master thread of process 0, only, open
562    
563  C Gather array and write it to file, one vertical level at a time  C Gather array and write it to file, one vertical level at a time
564         DO k=1,nNz         DO k=1,nNz
565  C Loop over all processors      C Loop over all processors
566          do jp=1,nPy          do jp=1,nPy
567          do ip=1,nPx          do ip=1,nPx
568          DO bj = myByLo(myThid), myByHi(myThid)          DO bj = myByLo(myThid), myByHi(myThid)
# Line 590  C Loop over all processors Line 579  C Loop over all processors
579          enddo          enddo
580          enddo          enddo
581          _BEGIN_MASTER( myThid )          _BEGIN_MASTER( myThid )
582           IF( mpiMyId .EQ. 0 ) THEN           IF( myProcId .EQ. 0 ) THEN
583            irec=k+nNz*(irecord-1)            irec=k+nNz*(irecord-1)
584            if (filePrec .eq. precFloat32) then            if (filePrec .eq. precFloat32) then
585             DO J=1,Ny             DO J=1,Ny
# Line 624  C Loop over all processors Line 613  C Loop over all processors
613    
614  C Close data-file and create meta-file  C Close data-file and create meta-file
615         _BEGIN_MASTER( myThid )         _BEGIN_MASTER( myThid )
616          IF( mpiMyId .EQ. 0 ) THEN          IF( myProcId .EQ. 0 ) THEN
617           close( dUnit )           close( dUnit )
618           write(metaFName,'(2a)') fName(1:IL),'.meta'           write(metaFName,'(2a)') fName(1:IL),'.meta'
619           dimList(1,1)=Nx           dimList(1,1)=Nx
# Line 636  C Close data-file and create meta-file Line 625  C Close data-file and create meta-file
625           dimList(1,3)=nNz           dimList(1,3)=nNz
626           dimList(2,3)=1           dimList(2,3)=1
627           dimList(3,3)=nNz           dimList(3,3)=nNz
628           ndims=3           nDims=3
629           if (nNz .EQ. 1) ndims=2           if (nNz .EQ. 1) nDims=2
630           call MDSWRITEMETA( metaFName, dataFName,           map2gl(1) = 0
631       &     filePrec, ndims, dimList, irecord, myIter, mythid )           map2gl(2) = 1
632             CALL MDS_WRITE_META(
633         I              metaFName, dataFName, the_run_name, ' ',
634         I              filePrec, nDims, dimList, map2gl, 0, blank8c,
635         I              0, dummyRL, irecord, myIter, myThid )
636          ENDIF          ENDIF
637         _END_MASTER( myThid )         _END_MASTER( myThid )
638  C To be safe, make other processes wait for I/O completion  C To be safe, make other processes wait for I/O completion
# Line 650  C To be safe, make other processes wait Line 643  C To be safe, make other processes wait
643  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
644  cph-usesingle)  cph-usesingle)
645    
646  C Loop over all processors      C Loop over all processors
647        do jp=1,nPy        do jp=1,nPy
648        do ip=1,nPx        do ip=1,nPx
649  C Loop over all tiles  C Loop over all tiles
# Line 746  C Create meta-file for each tile if we a Line 739  C Create meta-file for each tile if we a
739           dimList(1,3)=Nr           dimList(1,3)=Nr
740           dimList(2,3)=1           dimList(2,3)=1
741           dimList(3,3)=Nr           dimList(3,3)=Nr
742           ndims=3           nDims=3
743           if (Nr .EQ. 1) ndims=2           if (Nr .EQ. 1) nDims=2
744           call MDSWRITEMETA( metaFName, dataFName,           map2gl(1) = 0
745       &     filePrec, ndims, dimList, irecord, myIter, mythid )           map2gl(2) = 1
746             CALL MDS_WRITE_META(
747         I              metaFName, dataFName, the_run_name, ' ',
748         I              filePrec, nDims, dimList, map2gl, 0, blank8c,
749         I              0, dummyRL, irecord, myIter, myThid )
750  C End of bi,bj loops  C End of bi,bj loops
751         enddo         enddo
752        enddo        enddo
# Line 766  C endif useSingleCpuIO Line 763  C endif useSingleCpuIO
763  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
764  cph-usesingle)  cph-usesingle)
765    
766    #else /* ALLOW_CTRL */
767          STOP 'ABNORMAL END: S/R MDSWRITEFIELD_3D_GL is empty'
768  #endif /* ALLOW_CTRL */  #endif /* ALLOW_CTRL */
769  C     ------------------------------------------------------------------  C     ------------------------------------------------------------------
770        return        RETURN
771        end        END
772  C=======================================================================  
773    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
774    
 C=======================================================================  
775        SUBROUTINE MDSREADFIELD_2D_GL(        SUBROUTINE MDSREADFIELD_2D_GL(
776       I   fName,       I   fName,
777       I   filePrec,       I   filePrec,
# Line 813  C Created: 03/16/99 adcroft@mit.edu Line 812  C Created: 03/16/99 adcroft@mit.edu
812  C Global variables / common blocks  C Global variables / common blocks
813  #include "SIZE.h"  #include "SIZE.h"
814  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "EESUPPORT.h"  
815  #include "PARAMS.h"  #include "PARAMS.h"
816    
817  C Routine arguments  C Routine arguments
# Line 894  C Assign a free unit number as the I/O c Line 892  C Assign a free unit number as the I/O c
892    
893  C master thread of process 0, only, opens a global file  C master thread of process 0, only, opens a global file
894  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
895          IF( mpiMyId .EQ. 0 ) THEN          IF( myProcId .EQ. 0 ) THEN
896  #else  #else
897          IF ( .TRUE. ) THEN          IF ( .TRUE. ) THEN
898  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
# Line 918  C Otherwise stop program. Line 916  C Otherwise stop program.
916            open( dUnit, file=dataFName, status='old',            open( dUnit, file=dataFName, status='old',
917       &         access='direct', recl=length_of_rec )       &         access='direct', recl=length_of_rec )
918           else           else
919            write(msgbuf,'(2a)')            write(msgbuf,'(2a)')
920       &      ' MDSREADFIELD: filename: ',dataFName(1:IL)       &      ' MDSREADFIELD: filename: ',dataFName(1:IL)
921            call print_message( msgbuf, standardmessageunit,            call print_message( msgbuf, standardmessageunit,
922       &                        SQUEEZE_RIGHT , mythid)       &                        SQUEEZE_RIGHT , mythid)
# Line 974  C If we are reading from a global file t Line 972  C If we are reading from a global file t
972         fileIsOpen=.TRUE.         fileIsOpen=.TRUE.
973        endif        endif
974    
975  C Loop over all processors      C Loop over all processors
976        do jp=1,nPy        do jp=1,nPy
977        do ip=1,nPx        do ip=1,nPx
978  C Loop over all tiles  C Loop over all tiles
# Line 1100  c      else of if ( .not. ( globalFile . Line 1098  c      else of if ( .not. ( globalFile .
1098         DO k=1,nLocz         DO k=1,nLocz
1099    
1100  #ifdef ALLOW_USE_MPI  #ifdef ALLOW_USE_MPI
1101           IF( mpiMyId .EQ. 0 ) THEN           IF( myProcId .EQ. 0 ) THEN
1102  #else  #else
1103           IF ( .TRUE. ) THEN           IF ( .TRUE. ) THEN
1104  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
# Line 1158  c      end of if ( .not. ( globalFile .a Line 1156  c      end of if ( .not. ( globalFile .a
1156    
1157        _END_MASTER( myThid )        _END_MASTER( myThid )
1158    
1159    #else /* ALLOW_CTRL */
1160          STOP 'ABNORMAL END: S/R MDSREADFIELD_2D_GL is empty'
1161  #endif /* ALLOW_CTRL */  #endif /* ALLOW_CTRL */
1162  C     ------------------------------------------------------------------  C     ------------------------------------------------------------------
1163        return        RETURN
1164        end        END
1165  C=======================================================================  
1166    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
1167    
 C=======================================================================  
1168        SUBROUTINE MDSWRITEFIELD_2D_GL(        SUBROUTINE MDSWRITEFIELD_2D_GL(
1169       I   fName,       I   fName,
1170       I   filePrec,       I   filePrec,
# Line 1215  C          open(dUnit, ..., status='old' Line 1215  C          open(dUnit, ..., status='old'
1215  C Global variables / common blocks  C Global variables / common blocks
1216  #include "SIZE.h"  #include "SIZE.h"
1217  #include "EEPARAMS.h"  #include "EEPARAMS.h"
 #include "EESUPPORT.h"  
1218  #include "PARAMS.h"  #include "PARAMS.h"
1219    
1220  C Routine arguments  C Routine arguments
# Line 1243  C Local variables Line 1242  C Local variables
1242        Real*4 r4seg(sNx)        Real*4 r4seg(sNx)
1243        Real*8 r8seg(sNx)        Real*8 r8seg(sNx)
1244        _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nLocz,nSx,nSy)        _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nLocz,nSx,nSy)
1245        integer dimList(3,3),ndims        INTEGER dimList(3,3), nDims, map2gl(2)
1246          _RL dummyRL(1)
1247          CHARACTER*8 blank8c
1248        integer length_of_rec        integer length_of_rec
1249        logical fileIsOpen        logical fileIsOpen
1250        character*(max_len_mbuf) msgbuf        character*(max_len_mbuf) msgbuf
# Line 1263  CMM( Line 1264  CMM(
1264        integer pIL        integer pIL
1265  CMM)  CMM)
1266    
1267          DATA dummyRL(1) / 0. _d 0 /
1268          DATA blank8c / '        ' /
1269    
1270  C     ------------------------------------------------------------------  C     ------------------------------------------------------------------
1271    
1272  C Only do I/O if I am the master thread  C Only do I/O if I am the master thread
# Line 1306  C globalFile is too slow, then try using Line 1310  C globalFile is too slow, then try using
1310    
1311  C Master thread of process 0, only, opens a global file  C Master thread of process 0, only, opens a global file
1312         _BEGIN_MASTER( myThid )         _BEGIN_MASTER( myThid )
1313          IF( mpiMyId .EQ. 0 ) THEN          IF( myProcId .EQ. 0 ) THEN
1314           write(dataFname,'(2a)') fName(1:IL),'.data'           write(dataFname,'(2a)') fName(1:IL),'.data'
1315           length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid)           length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid)
1316           if (irecord .EQ. 1) then           if (irecord .EQ. 1) then
# Line 1321  C Master thread of process 0, only, open Line 1325  C Master thread of process 0, only, open
1325    
1326  C Gather array and write it to file, one vertical level at a time  C Gather array and write it to file, one vertical level at a time
1327         DO k=1,nLocz         DO k=1,nLocz
1328  C Loop over all processors      C Loop over all processors
1329          do jp=1,nPy          do jp=1,nPy
1330          do ip=1,nPx          do ip=1,nPx
1331          DO bj = myByLo(myThid), myByHi(myThid)          DO bj = myByLo(myThid), myByHi(myThid)
# Line 1338  C Loop over all processors Line 1342  C Loop over all processors
1342          enddo          enddo
1343          enddo          enddo
1344          _BEGIN_MASTER( myThid )          _BEGIN_MASTER( myThid )
1345           IF( mpiMyId .EQ. 0 ) THEN           IF( myProcId .EQ. 0 ) THEN
1346            irec=k+nLocz*(irecord-1)            irec=k+nLocz*(irecord-1)
1347            if (filePrec .eq. precFloat32) then            if (filePrec .eq. precFloat32) then
1348             DO J=1,Ny             DO J=1,Ny
# Line 1372  C Loop over all processors Line 1376  C Loop over all processors
1376    
1377  C Close data-file and create meta-file  C Close data-file and create meta-file
1378         _BEGIN_MASTER( myThid )         _BEGIN_MASTER( myThid )
1379          IF( mpiMyId .EQ. 0 ) THEN          IF( myProcId .EQ. 0 ) THEN
1380           close( dUnit )           close( dUnit )
1381           write(metaFName,'(2a)') fName(1:IL),'.meta'           write(metaFName,'(2a)') fName(1:IL),'.meta'
1382           dimList(1,1)=Nx           dimList(1,1)=Nx
# Line 1384  C Close data-file and create meta-file Line 1388  C Close data-file and create meta-file
1388           dimList(1,3)=nLocz           dimList(1,3)=nLocz
1389           dimList(2,3)=1           dimList(2,3)=1
1390           dimList(3,3)=nLocz           dimList(3,3)=nLocz
1391           ndims=3           nDims=3
1392           if (nLocz .EQ. 1) ndims=2           if (nLocz .EQ. 1) nDims=2
1393           call MDSWRITEMETA( metaFName, dataFName,           map2gl(1) = 0
1394       &     filePrec, ndims, dimList, irecord, myIter, mythid )           map2gl(2) = 1
1395             CALL MDS_WRITE_META(
1396         I              metaFName, dataFName, the_run_name, ' ',
1397         I              filePrec, nDims, dimList, map2gl, 0, blank8c,
1398         I              0, dummyRL, irecord, myIter, myThid )
1399          ENDIF          ENDIF
1400         _END_MASTER( myThid )         _END_MASTER( myThid )
1401  C To be safe, make other processes wait for I/O completion  C To be safe, make other processes wait for I/O completion
# Line 1398  C To be safe, make other processes wait Line 1406  C To be safe, make other processes wait
1406  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
1407  cph-usesingle)  cph-usesingle)
1408    
1409  C Loop over all processors      C Loop over all processors
1410        do jp=1,nPy        do jp=1,nPy
1411        do ip=1,nPx        do ip=1,nPx
1412  C Loop over all tiles  C Loop over all tiles
# Line 1494  C Create meta-file for each tile if we a Line 1502  C Create meta-file for each tile if we a
1502           dimList(1,3)=Nr           dimList(1,3)=Nr
1503           dimList(2,3)=1           dimList(2,3)=1
1504           dimList(3,3)=Nr           dimList(3,3)=Nr
1505           ndims=3           nDims=3
1506           if (nLocz .EQ. 1) ndims=2           if (nLocz .EQ. 1) nDims=2
1507           call MDSWRITEMETA( metaFName, dataFName,           map2gl(1) = 0
1508       &     filePrec, ndims, dimList, irecord, myIter, mythid )           map2gl(2) = 1
1509             CALL MDS_WRITE_META(
1510         I              metaFName, dataFName, the_run_name, ' ',
1511         I              filePrec, nDims, dimList, map2gl, 0, blank8c,
1512         I              0, dummyRL, irecord, myIter, myThid )
1513  C End of bi,bj loops  C End of bi,bj loops
1514         enddo         enddo
1515        enddo        enddo
# Line 1512  C endif useSingleCpuIO Line 1524  C endif useSingleCpuIO
1524        endif        endif
1525  #endif /* ALLOW_USE_MPI */  #endif /* ALLOW_USE_MPI */
1526    
1527    #else /* ALLOW_CTRL */
1528          STOP 'ABNORMAL END: S/R MDSWRITEFIELD_2D_GL is empty'
1529  #endif /* ALLOW_CTRL */  #endif /* ALLOW_CTRL */
1530  C     ------------------------------------------------------------------  C     ------------------------------------------------------------------
1531        return        RETURN
1532        end        END
 C=======================================================================  

Legend:
Removed from v.1.16  
changed lines
  Added in v.1.17

  ViewVC Help
Powered by ViewVC 1.1.22