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

Contents of /MITgcm/pkg/mdsio/mdsio_writevec_loc.F

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


Revision 1.9 - (show annotations) (download)
Sun Jan 13 22:43:53 2013 UTC (11 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64c, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.8: +2 -2 lines
- add missing value argument to S/R MDS_WRITE_META argument list

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writevec_loc.F,v 1.8 2011/06/07 22:30:29 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MDS_WRITEVEC_LOC
8 C !INTERFACE:
9 SUBROUTINE MDS_WRITEVEC_LOC(
10 I fName,
11 I filePrec,
12 U ioUnit,
13 I arrType,
14 I nSize,
15 I fldRL, fldRS,
16 I bi, bj,
17 I irecord,
18 I myIter,
19 I myThid )
20
21 C !DESCRIPTION:
22 C Arguments:
23 C
24 C fName string :: base name for file to written
25 C filePrec integer :: number of bits per word in file (32 or 64)
26 C ioUnit integer :: fortran file IO unit
27 C nSize integer :: number of elements from input array "fldRL/RS" to be written
28 C arrType char(2) :: which array (fldRL/RS) to write, either "RL" or "RS"
29 C fldRL ( RL ) :: array to write if arrType="RL", fldRL(nSize)
30 C fldRS ( RS ) :: array to write if arrType="RS", fldRS(nSize)
31 C bi,bj integer :: tile indices (if tiled array) or 0,0 if not a tiled array
32 C irecord integer :: record number to WRITE =|irecord|
33 C myIter integer :: time step number
34 C myThid integer :: my Thread Id number
35 C
36 C MDS_WRITEVEC_LOC according to ioUnit:
37 C ioUnit = 0 : open file, write and close the file (return ioUnit=0).
38 C ioUnit =-1 : open file, write and leave it open (return IO unit in ioUnit)
39 C ioUnit > 0 : assume file "ioUnit" is open, and write to it.
40 C MDS_WRITEVEC_LOC writes either to a file of the form "fName.data" and
41 C "fName.meta" if bi=bj=0. Otherwise it writes to MDS tiled files of the
42 C form "fName.xxx.yyy.data" and "fName.xxx.yyy.meta".
43 C If irecord>0, a meta-file is created (skipped if irecord<0).
44 C The precision of the file is described by filePrec, set either
45 C to floatPrec32 or floatPrec64.
46 C |irecord|=iRec is the record number to be written and must be >=1.
47
48 C !USES:
49 IMPLICIT NONE
50
51 C Global variables / common blocks
52 #include "SIZE.h"
53 #include "EEPARAMS.h"
54 #include "PARAMS.h"
55 #ifdef ALLOW_FIZHI
56 # include "fizhi_SIZE.h"
57 #endif /* ALLOW_FIZHI */
58 #include "MDSIO_BUFF_3D.h"
59
60 C !INPUT/OUTPUT PARAMETERS:
61 CHARACTER*(*) fName
62 INTEGER ioUnit
63 INTEGER filePrec
64 CHARACTER*(2) arrType
65 INTEGER nSize
66 _RL fldRL(*)
67 _RS fldRS(*)
68 INTEGER bi,bj
69 INTEGER irecord
70 INTEGER myIter
71 INTEGER myThid
72
73 C !FUNCTIONS:
74 INTEGER ILNBLNK
75 INTEGER MDS_RECLEN
76 EXTERNAL ILNBLNK
77 EXTERNAL MDS_RECLEN
78
79 C !LOCAL VARIABLES:
80 CHARACTER*(MAX_LEN_FNAM) dataFName, metaFName, pfName
81 CHARACTER*(MAX_LEN_MBUF) msgBuf
82 LOGICAL fileIsOpen
83 INTEGER iG,jG,iRec,dUnit,IL,pIL
84 INTEGER dimList(3,3), nDims, map2gl(2)
85 INTEGER length_of_rec
86 INTEGER buffSize
87 _RL dummyRL(1)
88 CHARACTER*8 blank8c
89 CEOP
90
91 DATA dummyRL(1) / 0. _d 0 /
92 DATA blank8c / ' ' /
93 DATA map2gl / 0, 1 /
94
95 C We write a non-tiled array (bi=bj=0) only 1 time (if ProcId=0):
96 IF ( myProcId.EQ.0 .OR. bi.NE.0 .OR. bj.NE.0 ) THEN
97
98 C Only DO I/O IF I am the master thread
99 _BEGIN_MASTER( myThid )
100
101 C Assume nothing
102 fileIsOpen = .FALSE.
103 IL = ILNBLNK( fName )
104 iRec = ABS(irecord)
105
106 C Record number must be >= 1
107 IF ( iRec.LT.1 ) THEN
108 WRITE(msgBuf,'(A,I9)')
109 & ' MDS_WRITEVEC_LOC: argument irecord = ',irecord
110 CALL PRINT_ERROR( msgBuf, myThid )
111 WRITE(msgBuf,'(A)')
112 & ' MDS_WRITEVEC_LOC: invalid value for irecord'
113 CALL PRINT_ERROR( msgBuf, myThid )
114 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
115 ENDIF
116
117 C Check buffer size
118 buffSize = sNx*sNy*size3dBuf*nSx*nSy
119 IF ( nSize.GT.buffSize ) THEN
120 WRITE(msgBuf,'(3A)')
121 & ' MDS_WRITEVEC_LOC: writing to file "', fName(1:IL), '":'
122 CALL PRINT_ERROR( msgBuf, myThid )
123 WRITE(msgBuf,'(A,I9)')
124 & ' MDS_WRITEVEC_LOC: dim of array to write=', nSize
125 CALL PRINT_ERROR( msgBuf, myThid )
126 WRITE(msgBuf,'(A,I9)')
127 & ' MDS_WRITEVEC_LOC: exceeds buffer size=', buffSize
128 CALL PRINT_ERROR( msgBuf, myThid )
129 WRITE(msgBuf,'(A)')
130 & ' increase "size3dBuf" in "MDSIO_BUFF_3D.h" and recompile'
131 CALL PRINT_ERROR( msgBuf, myThid )
132 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
133 ENDIF
134
135 C Assign special directory
136 IF ( mdsioLocalDir .NE. ' ' ) THEN
137 pIL = ILNBLNK( mdsioLocalDir )
138 WRITE(pFname,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
139 pIL = IL + pIL
140 ELSE
141 WRITE(pFname,'(A)') fName(1:IL)
142 pIL = IL
143 ENDIF
144
145 IF ( ioUnit.GT.0 ) THEN
146 C- Assume file Unit is already open with correct Rec-Length & Precision
147 fileIsOpen = .TRUE.
148 dUnit = ioUnit
149 ELSE
150 C- Need to open file IO unit with File-name, Rec-Length & Precision
151
152 C Assign a free unit number as the I/O channel for this routine
153 CALL MDSFINDUNIT( dUnit, myThid )
154
155 C-- Set the file Name:
156 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
157 C- we are writing a non-tiled array (bi=bj=0):
158 WRITE(dataFname,'(2A)') fName(1:IL),'.data'
159 ELSE
160 C- we are writing a tiled array (bi>0,bj>0):
161 iG=bi+(myXGlobalLo-1)/sNx
162 jG=bj+(myYGlobalLo-1)/sNy
163 WRITE(dataFname,'(2A,I3.3,A,I3.3,A)')
164 & pfName(1:pIL),'.',iG,'.',jG,'.data'
165 ENDIF
166
167 C-- Open the file:
168 length_of_rec=MDS_RECLEN( filePrec, nSize, myThid )
169 IF (iRec .EQ. 1) THEN
170 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
171 & access='direct', recl=length_of_rec )
172 fileIsOpen=.TRUE.
173 ELSE
174 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
175 & access='direct', recl=length_of_rec )
176 fileIsOpen=.TRUE.
177 ENDIF
178 IF ( debugLevel.GE.debLevC ) THEN
179 WRITE(msgBuf,'(2A)')
180 & ' MDS_WRITEVEC_LOC: open file: ',dataFname(1:pIL+13)
181 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
182 & SQUEEZE_RIGHT , 1)
183 ENDIF
184 C- End if block: File Unit is already open / Need to open it
185 ENDIF
186
187 IF (fileIsOpen) THEN
188 IF ( arrType.EQ.'RS' ) THEN
189 CALL MDS_WR_REC_RS( fldRS, shared3dBuf_r4, shared3dBuf_r8,
190 I filePrec, dUnit, iRec, nSize, myThid )
191 ELSEIF ( arrType.EQ.'RL' ) THEN
192 CALL MDS_WR_REC_RL( fldRL, shared3dBuf_r4, shared3dBuf_r8,
193 I filePrec, dUnit, iRec, nSize, myThid )
194 ELSE
195 WRITE(msgBuf,'(A)')
196 & ' MDS_WRITEVEC_LOC: illegal value for arrType'
197 CALL PRINT_ERROR( msgBuf, myThid )
198 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
199 ENDIF
200 ELSE
201 WRITE(msgBuf,'(A)')
202 & ' MDS_WRITEVEC_LOC: should never reach this point'
203 CALL PRINT_ERROR( msgBuf, myThid )
204 STOP 'ABNORMAL END: S/R MDS_WRITEVEC_LOC'
205 ENDIF
206
207 C If we were writing to a tiled MDS file then we close it here
208 IF ( fileIsOpen .AND. ioUnit.EQ.0 ) THEN
209 CLOSE( dUnit )
210 fileIsOpen = .FALSE.
211 ENDIF
212 IF ( ioUnit.EQ.-1 ) ioUnit = dUnit
213
214 IF ( irecord.GT.0 ) THEN
215 C Create meta-file for each tile IF we are tiling
216 IF ( bi.EQ.0 .AND. bj.EQ.0 ) THEN
217 C-- we are writing a non-tiled array (bi=bj=0):
218 WRITE(metaFname,'(2A)') fName(1:IL),'.meta'
219 dimList(1,1)=1
220 dimList(2,1)=1
221 dimList(3,1)=1
222 dimList(1,2)=1
223 dimList(2,2)=1
224 dimList(3,2)=1
225 ELSE
226 C-- we are writing a tiled array (bi>0,bj>0):
227 iG=bi+(myXGlobalLo-1)/sNx
228 jG=bj+(myYGlobalLo-1)/sNy
229 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
230 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
231 dimList(1,1)=nSx*nPx
232 dimList(2,1)=iG
233 dimList(3,1)=iG
234 dimList(1,2)=nSy*nPy
235 dimList(2,2)=jG
236 dimList(3,2)=jG
237 ENDIF
238 dimList(1,3)=nSize
239 dimList(2,3)=1
240 dimList(3,3)=nSize
241 nDims=3
242 IF ( nSize.EQ.1 ) nDims=2
243 CALL MDS_WRITE_META(
244 I metaFName, dataFName, the_run_name, ' ',
245 I filePrec, nDims, dimList, map2gl, 0, blank8c,
246 I 0, dummyRL, oneRL, irecord, myIter, myThid )
247 ENDIF
248
249 _END_MASTER( myThid )
250 ENDIF
251
252 RETURN
253 END

  ViewVC Help
Powered by ViewVC 1.1.22