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

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

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


Revision 1.6 - (show annotations) (download)
Wed May 6 02:42:49 2009 UTC (16 years, 1 month ago) by jmc
Branch: MAIN
Changes since 1.5: +57 -123 lines
new S/R to map global io-buffer to global model array ; used by both
 mdsio_write_field.F and mdsio_read_field.F (useSingleCpuIO).

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_write_field.F,v 1.5 2008/12/30 00:13:35 jahn Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MDS_WRITE_FIELD
8 C !INTERFACE:
9 SUBROUTINE MDS_WRITE_FIELD(
10 I fName,
11 I filePrec,
12 I globalFile,
13 I useCurrentDir,
14 I arrType,
15 I kSize,kLo,kHi,
16 I arr,
17 I jrecord,
18 I myIter,
19 I myThid )
20
21 C !DESCRIPTION:
22 C Arguments:
23 C
24 C fName (string) :: base name for file to write
25 C filePrec (integer) :: number of bits per word in file (32 or 64)
26 C globalFile (logical):: selects between writing a global or tiled file
27 C useCurrentDir(logic):: always write to the current directory (even if
28 C "mdsioLocalDir" is set)
29 C arrType (char(2)) :: declaration of "arr": either "RS" or "RL"
30 C kSize (integer) :: size of third dimension: normally either 1 or Nr
31 C kLo (integer) :: 1rst vertical level (of array "arr") to write
32 C kHi (integer) :: last vertical level (of array "arr") to write
33 C arr ( RS/RL ) :: array to write, arr(:,:,kSize,:,:)
34 C irecord (integer) :: record number to write
35 C myIter (integer) :: time step number
36 C myThid (integer) :: thread identifier
37 C
38 C MDS_WRITE_FIELD creates either a file of the form "fName.data" and
39 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
40 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
41 C "fName.xxx.yyy.meta". If jrecord > 0, a meta-file is created.
42 C Currently, the meta-files are not read because it is difficult
43 C to parse files in fortran. We should read meta information before
44 C adding records to an existing multi-record file.
45 C The precision of the file is decsribed by filePrec, set either
46 C to floatPrec32 or floatPrec64. The precision or declaration of
47 C the array argument must be consistently described by the char*(2)
48 C string arrType, either "RS" or "RL".
49 C (kSize,kLo,kHi) allows for both 2-D and 3-D arrays to be handled, with
50 C the option to only write a sub-set of consecutive vertical levels (from
51 C kLo to kHi); (kSize,kLo,kHi)=(1,1,1) implies a 2-D model field and
52 C (kSize,kLo,kHi)=(Nr,1,Nr) implies a 3-D model field.
53 C irecord=|jrecord| is the record number to be written and must be >= 1.
54 C NOTE: It is currently assumed that the highest record number in the file
55 C was the last record written. Nor is there a consistency check between the
56 C routine arguments and file, i.e., if you write record 2 after record 4
57 C the meta information will record the number of records to be 2. This,
58 C again, is because we have read the meta information. To be fixed.
59 C
60 C Created: 03/16/99 adcroft@mit.edu
61 C Changed: 01/06/02 menemenlis@jpl.nasa.gov
62 C added useSingleCpuIO hack
63 C changed: 1/23/04 afe@ocean.mit.edu
64 C added exch2 handling -- yes, the globalfile logic is nuts
65 CEOP
66
67 C !USES:
68 IMPLICIT NONE
69 C Global variables / common blocks
70 #include "SIZE.h"
71 #include "EEPARAMS.h"
72 #include "PARAMS.h"
73 #ifdef ALLOW_EXCH2
74 #include "W2_EXCH2_TOPOLOGY.h"
75 #include "W2_EXCH2_PARAMS.h"
76 #endif /* ALLOW_EXCH2 */
77 #include "MDSIO_SCPU.h"
78
79 C !INPUT PARAMETERS:
80 CHARACTER*(*) fName
81 INTEGER filePrec
82 LOGICAL globalFile
83 LOGICAL useCurrentDir
84 CHARACTER*(2) arrType
85 INTEGER kSize, kLo, kHi
86 cph(
87 cph Real arr(*)
88 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,kSize,nSx,nSy)
89 cph)
90 INTEGER jrecord
91 INTEGER myIter
92 INTEGER myThid
93 C !OUTPUT PARAMETERS:
94
95 C !FUNCTIONS
96 INTEGER ILNBLNK
97 INTEGER MDS_RECLEN
98 LOGICAL MASTER_CPU_IO
99 EXTERNAL ILNBLNK
100 EXTERNAL MDS_RECLEN
101 EXTERNAL MASTER_CPU_IO
102
103 C !LOCAL VARIABLES:
104 CHARACTER*(MAX_LEN_FNAM) dataFName,metaFName,pfName
105 CHARACTER*(MAX_LEN_MBUF) msgBuf
106 LOGICAL fileIsOpen
107 LOGICAL iAmDoingIO
108 LOGICAL writeMetaF
109 LOGICAL zeroBuff
110 INTEGER xSize, ySize
111 INTEGER irecord
112 INTEGER iG,jG,bi,bj,i,j,k,nNz
113 INTEGER irec,dUnit,IL,pIL
114 INTEGER dimList(3,3), nDims, map2gl(2)
115 INTEGER iGjLoc, jGjLoc
116 INTEGER length_of_rec
117 Real*4 r4seg(sNx)
118 Real*8 r8seg(sNx)
119 #ifdef ALLOW_EXCH2
120 c INTEGER tGy,tGx,tNy,tNx,tN
121 INTEGER tGy,tGx, tNx,tN
122 INTEGER global_nTx
123 #endif /* ALLOW_EXCH2 */
124 INTEGER tNy
125
126 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
127 C Set dimensions:
128 xSize = Nx
129 ySize = Ny
130 #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
131 xSize = exch2_global_Nx
132 ySize = exch2_global_Ny
133 #endif
134
135 C- default:
136 iGjLoc = 0
137 jGjLoc = 1
138
139 C Assume nothing
140 fileIsOpen = .FALSE.
141 IL = ILNBLNK( fName )
142 pIL = ILNBLNK( mdsioLocalDir )
143 nNz = 1 + kHi - kLo
144 irecord = ABS(jrecord)
145 writeMetaF = jrecord.GT.0
146
147 C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO):
148 iAmDoingIO = MASTER_CPU_IO(myThid)
149
150 C Only do I/O if I am the master thread
151 IF ( iAmDoingIO ) THEN
152
153 C Record number must be >= 1
154 IF (irecord .LT. 1) THEN
155 WRITE(msgBuf,'(A,I9.8)')
156 & ' MDS_WRITE_FIELD: argument irecord = ',irecord
157 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
158 & SQUEEZE_RIGHT , myThid)
159 WRITE(msgBuf,'(A)')
160 & ' MDS_WRITE_FIELD: invalid value for irecord'
161 CALL PRINT_ERROR( msgBuf, myThid )
162 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
163 ENDIF
164 C check for valid sub-set of levels:
165 IF ( kLo.LT.1 .OR. kHi.GT.kSize ) THEN
166 WRITE(msgBuf,'(3(A,I6))')
167 & ' MDS_WRITE_FIELD: arguments kSize=', kSize,
168 & ' , kLo=', kLo, ' , kHi=', kHi
169 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
170 & SQUEEZE_RIGHT , myThid)
171 WRITE(msgBuf,'(A)')
172 & ' MDS_WRITE_FIELD: invalid sub-set of levels'
173 CALL PRINT_ERROR( msgBuf, myThid )
174 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
175 ENDIF
176
177 C Assign special directory
178 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
179 pfName = fName
180 ELSE
181 WRITE(pfName,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
182 ENDIF
183 pIL=ILNBLNK( pfName )
184
185 C Assign a free unit number as the I/O channel for this routine
186 CALL MDSFINDUNIT( dUnit, myThid )
187
188 C- endif iAmDoingIO
189 ENDIF
190
191 C If option globalFile is desired but does not work or if
192 C globalFile is too slow, then try using single-CPU I/O.
193 IF (useSingleCpuIO) THEN
194
195 C Master thread of process 0, only, opens a global file
196 IF ( iAmDoingIO ) THEN
197 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
198 length_of_rec=MDS_RECLEN(filePrec,xSize*ySize,myThid)
199 IF (irecord .EQ. 1) THEN
200 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
201 & access='direct', recl=length_of_rec )
202 ELSE
203 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
204 & access='direct', recl=length_of_rec )
205 ENDIF
206 ENDIF
207
208 C Gather array and WRITE it to file, one vertical level at a time
209 DO k=kLo,kHi
210 C- copy from arr(level=k) to 2-D "local":
211 IF ( arrType.EQ.'RS' ) THEN
212 CALL MDS_PASStoRS(sharedLocalBuf,arr,k,kSize,.FALSE.,myThid)
213 ELSEIF ( arrType.EQ.'RL' ) THEN
214 CALL MDS_PASStoRL(sharedLocalBuf,arr,k,kSize,.FALSE.,myThid)
215 ELSE
216 WRITE(msgBuf,'(A)')
217 & ' MDS_WRITE_FIELD: illegal value for arrType'
218 CALL PRINT_ERROR( msgBuf, myThid )
219 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
220 ENDIF
221 CALL GATHER_2D( globalBuf, sharedLocalBuf, myThid )
222
223 IF ( iAmDoingIO ) THEN
224 C Map global model (real*8) array to the appropriate global io-buffer
225 zeroBuff = k.EQ.kLo
226 CALL MDS_MAP_GLOBAL(
227 U xy_buffer_r4, xy_buffer_r8,
228 U globalBuf,
229 I xSize, ySize, filePrec,
230 I .FALSE., zeroBuff )
231
232 irec=k+1-kLo+nNz*(irecord-1)
233 IF (filePrec .EQ. precFloat32) THEN
234 #ifdef _BYTESWAPIO
235 CALL MDS_BYTESWAPR4( xSize*ySize, xy_buffer_r4 )
236 #endif
237 WRITE(dUnit,rec=irec) ( xy_buffer_r4(i),i=1,xSize*ySize )
238 ELSEIF (filePrec .EQ. precFloat64) THEN
239 #ifdef _BYTESWAPIO
240 CALL MDS_BYTESWAPR8( xSize*ySize, xy_buffer_r8 )
241 #endif
242 WRITE(dUnit,rec=irec) ( xy_buffer_r8(i),i=1,xSize*ySize )
243 ELSE
244 WRITE(msgBuf,'(A)')
245 & ' MDS_WRITE_FIELD: illegal value for filePrec'
246 CALL PRINT_ERROR( msgBuf, myThid )
247 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
248 ENDIF
249 C- end if iAmDoingIO
250 ENDIF
251 C- end of k loop
252 ENDDO
253
254 C Close data-file
255 IF ( iAmDoingIO ) THEN
256 CLOSE( dUnit )
257 ENDIF
258
259 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
260 C--- else .NOT.useSingleCpuIO
261 ELSE
262
263 C Only do I/O if I am the master thread
264 IF ( iAmDoingIO ) THEN
265
266 C If we are writing to a global file then we open it here
267 IF (globalFile) THEN
268 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
269 IF (irecord .EQ. 1) THEN
270 length_of_rec=MDS_RECLEN( filePrec, sNx, myThid )
271 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
272 & access='direct', recl=length_of_rec )
273 fileIsOpen=.TRUE.
274 ELSE
275 length_of_rec=MDS_RECLEN( filePrec, sNx, myThid )
276 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
277 & access='direct', recl=length_of_rec )
278 fileIsOpen=.TRUE.
279 ENDIF
280 ENDIF
281
282 C Loop over all tiles
283 DO bj=1,nSy
284 DO bi=1,nSx
285 C If we are writing to a tiled MDS file then we open each one here
286 IF (.NOT. globalFile) THEN
287 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
288 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
289 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
290 & pfName(1:pIL),'.',iG,'.',jG,'.data'
291 IF (irecord .EQ. 1) THEN
292 length_of_rec=MDS_RECLEN( filePrec, sNx, myThid )
293 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
294 & access='direct', recl=length_of_rec )
295 fileIsOpen=.TRUE.
296 ELSE
297 length_of_rec=MDS_RECLEN( filePrec, sNx, myThid )
298 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
299 & access='direct', recl=length_of_rec )
300 fileIsOpen=.TRUE.
301 ENDIF
302 ENDIF
303
304 IF (fileIsOpen) THEN
305 tNy = sNy
306 #ifdef ALLOW_EXCH2
307 tN = W2_myTileList(bi)
308 tGy = exch2_tyGlobalo(tN)
309 tGx = exch2_txGlobalo(tN)
310 tNy = exch2_tNy(tN)
311 tNx = exch2_tNx(tN)
312 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
313 C- face x-size larger than glob-size : fold it
314 iGjLoc = 0
315 jGjLoc = exch2_mydNx(tN) / xSize
316 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
317 C- tile y-size larger than glob-size : make a long line
318 iGjLoc = exch2_mydNx(tN)
319 jGjLoc = 0
320 ELSE
321 C- default (face fit into global-IO-array)
322 iGjLoc = 0
323 jGjLoc = 1
324 ENDIF
325 global_nTx = exch2_global_Nx/tNx
326 #endif /* ALLOW_EXCH2 */
327 DO k=1,nNz
328 DO j=1,tNy
329 IF (globalFile) THEN
330 #ifdef ALLOW_EXCH2
331 irec = 1 + ( tGx-1 + (j-1)*iGjLoc )/tNx
332 & + ( tGy-1 + (j-1)*jGjLoc )*global_nTx
333 & + ( k-kLo + (irecord-1)*nNz
334 & )*ySize*global_nTx
335 #else /* ALLOW_EXCH2 */
336 iG = myXGlobalLo-1 + (bi-1)*sNx
337 jG = myYGlobalLo-1 + (bj-1)*sNy
338 irec= 1 + INT(iG/sNx) + nSx*nPx*(jG+j-1)
339 & + nSx*nPx*Ny*(k-kLo)
340 & + nSx*nPx*Ny*nNz*(irecord-1)
341 #endif /* ALLOW_EXCH2 */
342 ELSE
343 irec=j + sNy*(k-kLo) + sNy*nNz*(irecord-1)
344 ENDIF
345 IF (filePrec .EQ. precFloat32) THEN
346 IF (arrType .EQ. 'RS') THEN
347 CALL MDS_SEG4toRS( j,bi,bj,k,kSize, r4seg,.FALSE.,arr )
348 ELSEIF (arrType .EQ. 'RL') THEN
349 CALL MDS_SEG4toRL( j,bi,bj,k,kSize, r4seg,.FALSE.,arr )
350 ELSE
351 WRITE(msgBuf,'(A)')
352 & ' MDS_WRITE_FIELD: illegal value for arrType'
353 CALL PRINT_ERROR( msgBuf, myThid )
354 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
355 ENDIF
356 #ifdef _BYTESWAPIO
357 CALL MDS_BYTESWAPR4( sNx, r4seg )
358 #endif
359 WRITE(dUnit,rec=irec) r4seg
360 ELSEIF (filePrec .EQ. precFloat64) THEN
361 IF (arrType .EQ. 'RS') THEN
362 CALL MDS_SEG8toRS( j,bi,bj,k,kSize, r8seg,.FALSE.,arr )
363 ELSEIF (arrType .EQ. 'RL') THEN
364 CALL MDS_SEG8toRL( j,bi,bj,k,kSize, r8seg,.FALSE.,arr )
365 ELSE
366 WRITE(msgBuf,'(A)')
367 & ' MDS_WRITE_FIELD: illegal value for arrType'
368 CALL PRINT_ERROR( msgBuf, myThid )
369 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
370 ENDIF
371 #ifdef _BYTESWAPIO
372 CALL MDS_BYTESWAPR8( sNx, r8seg )
373 #endif
374 WRITE(dUnit,rec=irec) r8seg
375 ELSE
376 WRITE(msgBuf,'(A)')
377 & ' MDS_WRITE_FIELD: illegal value for filePrec'
378 CALL PRINT_ERROR( msgBuf, myThid )
379 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
380 ENDIF
381 C End of j loop
382 ENDDO
383 C End of k loop
384 ENDDO
385 ELSE
386 C fileIsOpen=F
387 WRITE(msgBuf,'(A)')
388 & ' MDS_WRITE_FIELD: I should never get to this point'
389 CALL PRINT_ERROR( msgBuf, myThid )
390 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
391 ENDIF
392 C If we were writing to a tiled MDS file then we close it here
393 IF (fileIsOpen .AND. (.NOT. globalFile)) THEN
394 CLOSE( dUnit )
395 fileIsOpen = .FALSE.
396 ENDIF
397 C Create meta-file for each tile if we are tiling
398 IF ( .NOT.globalFile .AND. writeMetaF ) THEN
399 iG=bi+(myXGlobalLo-1)/sNx
400 jG=bj+(myYGlobalLo-1)/sNy
401 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
402 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
403 #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
404 tN = W2_myTileList(bi)
405 dimList(1,1) = xSize
406 dimList(2,1) = exch2_txGlobalo(tN)
407 dimList(3,1) = exch2_txGlobalo(tN)+sNx-1
408 dimList(1,2) = ySize
409 dimList(2,2) = exch2_tyGlobalo(tN)
410 dimList(3,2) = exch2_tyGlobalo(tN)+sNy-1
411 #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
412 C- jmc: if MISSING_TILE_IO, keep meta files unchanged
413 C to stay consistent with global file structure
414 dimList(1,1) = Nx
415 dimList(2,1) = myXGlobalLo+(bi-1)*sNx
416 dimList(3,1) = myXGlobalLo+bi*sNx-1
417 dimList(1,2) = Ny
418 dimList(2,2) = myYGlobalLo+(bj-1)*sNy
419 dimList(3,2) = myYGlobalLo+bj*sNy-1
420 #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
421 dimList(1,3) = nNz
422 dimList(2,3) = 1
423 dimList(3,3) = nNz
424 nDims = 3
425 IF ( nNz.EQ.1 ) nDims = 2
426 map2gl(1) = iGjLoc
427 map2gl(2) = jGjLoc
428 CALL MDS_WRITE_META(
429 I metaFName, dataFName, the_run_name, ' ',
430 I filePrec, nDims,dimList,map2gl, 0, ' ',
431 I 0, UNSET_RL, irecord, myIter, myThid )
432 ENDIF
433 C End of bi,bj loops
434 ENDDO
435 ENDDO
436
437 C If global file was opened then close it
438 IF (fileIsOpen .AND. globalFile) THEN
439 CLOSE( dUnit )
440 fileIsOpen = .FALSE.
441 ENDIF
442
443 C- endif iAmDoingIO
444 ENDIF
445
446 C if useSingleCpuIO / else / end
447 ENDIF
448
449 C Create meta-file for the global-file (also if useSingleCpuIO)
450 IF ( writeMetaF .AND. iAmDoingIO .AND.
451 & (globalFile .OR. useSingleCpuIO) ) THEN
452 WRITE(metaFName,'(2A)') fName(1:IL),'.meta'
453 dimList(1,1) = xSize
454 dimList(2,1) = 1
455 dimList(3,1) = xSize
456 dimList(1,2) = ySize
457 dimList(2,2) = 1
458 dimList(3,2) = ySize
459 dimList(1,3) = nNz
460 dimList(2,3) = 1
461 dimList(3,3) = nNz
462 nDims = 3
463 IF ( nNz.EQ.1 ) nDims = 2
464 map2gl(1) = 0
465 map2gl(2) = 1
466 CALL MDS_WRITE_META(
467 I metaFName, dataFName, the_run_name, ' ',
468 I filePrec, nDims,dimList,map2gl, 0, ' ',
469 I 0, UNSET_RL, irecord, myIter, myThid )
470 c I metaFName, dataFName, the_run_name, titleLine,
471 c I filePrec, nDims, dimList, map2gl, nFlds, fldList,
472 c I nTimRec, timList, irecord, myIter, myThid )
473 ENDIF
474
475 C To be safe, make other processes wait for I/O completion
476 _BARRIER
477
478 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
479 RETURN
480 END

  ViewVC Help
Powered by ViewVC 1.1.22