/[MITgcm]/MITgcm/pkg/rw/write_local_rl.F
ViewVC logotype

Diff of /MITgcm/pkg/rw/write_local_rl.F

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

revision 1.6 by jmc, Tue Nov 13 19:41:05 2007 UTC revision 1.7 by jmc, Tue Jun 9 22:52:57 2009 UTC
# Line 3  C $Name$ Line 3  C $Name$
3    
4  #include "RW_OPTIONS.h"  #include "RW_OPTIONS.h"
5    
6    CBOP
7    C     !ROUTINE: WRITE_LOCAL_RL
8    C     !INTERFACE:
9        SUBROUTINE WRITE_LOCAL_RL(        SUBROUTINE WRITE_LOCAL_RL(
10       I          pref,suff,nNr,field,bi,bj,iRec,myIter,myThid)       I                 pref, suff, nNr, field,
11  C WRITE_LOCAL_RL is a "front-end" interface to the low-level I/O       I                 bi, bj, iRec, myIter, myThArg )
12  C routines. It assumes single record files.  
13    C     !DESCRIPTION:
14    C     Write "RL" type local-tile array "field" corresponding to tile bi,bj
15    C     to binary file (prefix,suffix) at record position "iRec".
16    
17    C     !USES:
18        IMPLICIT NONE        IMPLICIT NONE
19  C Global  C     Global variables / common blocks
20  #include "SIZE.h"  #include "SIZE.h"
21  #include "EEPARAMS.h"  #include "EEPARAMS.h"
22  #include "PARAMS.h"  #include "PARAMS.h"
23  C Arguments  
24    C     !INPUT/OUTPUT PARAMETERS:
25    C     pref    :: file name prefix
26    C     suff    :: file name suffix
27    C     nNr     :: Number of levels to write
28    C     field   :: field array to write
29    C     bi,bj   :: tile indices
30    C     iRec    :: record number in output file
31    C     myIter  :: Iteration number
32    C     myThArg :: thread argument (= my Thread Id or = 0 to simply
33    C                     write 1 tile without thread synchronisation)
34        CHARACTER*(*) pref,suff        CHARACTER*(*) pref,suff
35        INTEGER nNr        INTEGER nNr
36        _RL field(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nNr)        _RL field(1-Olx:sNx+Olx,1-Oly:sNy+Oly,nNr)
37        INTEGER bi,bj        INTEGER bi,bj
38        INTEGER iRec        INTEGER iRec
39        INTEGER myIter        INTEGER myIter
40        INTEGER myThid        INTEGER myThArg
41  C Functions  
42        INTEGER ILNBLNK,IFNBLNK  C     !FUNCTIONS
43  C Common        INTEGER  IFNBLNK, ILNBLNK
44          EXTERNAL IFNBLNK, ILNBLNK
45    
46    C     Common block
47        COMMON /RD_WR_FLD/ globalFile        COMMON /RD_WR_FLD/ globalFile
48        LOGICAL globalFile        LOGICAL globalFile
49  C Local  
50    C     !LOCAL VARIABLES:
51        LOGICAL useCurrentDir        LOGICAL useCurrentDir
52        CHARACTER*(2) fType        CHARACTER*(2) fType
       INTEGER s1Lo,s1Hi,s2Lo,s2Hi  
53        CHARACTER*(MAX_LEN_FNAM) fullName        CHARACTER*(MAX_LEN_FNAM) fullName
54          INTEGER s1Lo,s1Hi,s2Lo,s2Hi
55          INTEGER myThid
56    
57  C--   Build file name  C--   Build file name
58  C     Name has form 'prefix.suffix'  C     Name has form 'prefix.suffix'
# Line 50  C Line 73  C
73        fType='RL'        fType='RL'
74  #ifdef ALLOW_MDSIO  #ifdef ALLOW_MDSIO
75        IF (nSx.EQ.1.AND.nSy.EQ.1) THEN        IF (nSx.EQ.1.AND.nSy.EQ.1) THEN
76  C The hack below replaces MDS_WRITELOCAL with MDSWRITEFIELD_LOC for  C The hack below replaces MDS_WRITELOCAL with MDS_WRITE_FIELD for
77  C single-threaded execution because the former does not support the  C single-threaded execution because the former does not support the
78  C singleCpuIo option. This is a placeholder until MDS_WRITELOCAL  C singleCpuIo option. This is a placeholder until MDS_WRITELOCAL
79  C functionality is superseded by pkg/diagnostics.  C functionality is superseded by pkg/diagnostics.
80             myThid = MAX(myThArg,1)
81           CALL MDS_WRITE_FIELD(           CALL MDS_WRITE_FIELD(
82       I        fullName, writeBinaryPrec, globalFile, useCurrentDir,       I        fullName, writeBinaryPrec, globalFile, useCurrentDir,
83       I        fType, nNr, 1, nNr, field, iRec, myIter, myThid )       I        fType, nNr, 1, nNr, field, iRec, myIter, myThid )
84        ELSE        ELSE
85           CALL MDS_WRITELOCAL(           CALL MDS_WRITELOCAL(
86       I        fullName, writeBinaryPrec, globalFile,       I        fullName, writeBinaryPrec, globalFile,
87       I        fType, nNr, field, bi, bj, iRec, myIter, myThid )       I        fType, nNr, field, bi, bj, iRec, myIter, myThArg )
88        ENDIF        ENDIF
89  #endif  #endif
90    
91        RETURN        RETURN
92        END        END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.7

  ViewVC Help
Powered by ViewVC 1.1.22