/[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.2 - (show annotations) (download)
Mon Mar 19 02:30:49 2007 UTC (18 years, 3 months ago) by jmc
Branch: MAIN
Changes since 1.1: +112 -72 lines
to read/write compact global files: add parameter for mapping tile to global file.

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

  ViewVC Help
Powered by ViewVC 1.1.22