/[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.19 - (show annotations) (download)
Sun Jan 13 22:43:53 2013 UTC (11 years, 4 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, checkpoint65b, checkpoint65a
Changes since 1.18: +4 -4 lines
- add missing value argument to S/R MDS_WRITE_META argument list

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_write_field.F,v 1.18 2012/03/05 23:48:33 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 kSize,kLo,kHi,
16 I fldRL, fldRS,
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)) :: which array (fldRL/RS) to write, either "RL" or "RS"
30 C kSize (integer) :: size of third dimension: normally either 1 or Nr
31 C kLo (integer) :: 1rst vertical level (of array fldRL/RS) to write
32 C kHi (integer) :: last vertical level (of array fldRL/RS) to write
33 C fldRL ( RL ) :: array to write if arrType="RL", fldRL(:,:,kSize,:,:)
34 C fldRS ( RS ) :: array to write if arrType="RS", fldRS(:,:,kSize,:,:)
35 C irecord (integer) :: record number to write
36 C myIter (integer) :: time step number
37 C myThid (integer) :: thread identifier
38 C
39 C MDS_WRITE_FIELD creates either a file of the form "fName.data" and
40 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
41 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
42 C "fName.xxx.yyy.meta". If jrecord > 0, a meta-file is created.
43 C Currently, the meta-files are not read because it is difficult
44 C to parse files in fortran. We should read meta information before
45 C adding records to an existing multi-record file.
46 C The precision of the file is described by filePrec, set either
47 C to floatPrec32 or floatPrec64. The char*(2) string arrType, either
48 C "RL" or "RS", selects which array is written, either fldRL or fldRS.
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- Multi-threaded: Only Master thread does IO (and MPI calls) and get data
61 C from a shared buffer that any thread can copy to.
62 C- Convention regarding thread synchronisation (BARRIER):
63 C A per-thread (or per tile) partition of the 2-D shared-buffer (sharedLocBuf_r4/r8)
64 C is readily available => any access (e.g., by master-thread) to a portion
65 C owned by an other thread is put between BARRIER (protected).
66 C No thread partition exist for the 3-D shared buffer (shared3dBuf_r4/r8);
67 C Therefore, the 3-D buffer is considered to be owned by master-thread and
68 C any access by other than master thread is put between BARRIER (protected).
69 C
70 C Created: 03/16/99 adcroft@mit.edu
71 C Changed: 01/06/02 menemenlis@jpl.nasa.gov
72 C added useSingleCpuIO hack
73 C changed: 1/23/04 afe@ocean.mit.edu
74 C added exch2 handling -- yes, the globalfile logic is nuts
75 CEOP
76
77 C !USES:
78 IMPLICIT NONE
79 C Global variables / common blocks
80 #include "SIZE.h"
81 #include "EEPARAMS.h"
82 #include "PARAMS.h"
83 #ifdef ALLOW_EXCH2
84 # include "W2_EXCH2_SIZE.h"
85 # include "W2_EXCH2_TOPOLOGY.h"
86 # include "W2_EXCH2_PARAMS.h"
87 #endif /* ALLOW_EXCH2 */
88 #include "EEBUFF_SCPU.h"
89 #ifdef ALLOW_FIZHI
90 # include "fizhi_SIZE.h"
91 #endif /* ALLOW_FIZHI */
92 #include "MDSIO_BUFF_3D.h"
93
94 C !INPUT PARAMETERS:
95 CHARACTER*(*) fName
96 INTEGER filePrec
97 LOGICAL globalFile
98 LOGICAL useCurrentDir
99 CHARACTER*(2) arrType
100 INTEGER kSize, kLo, kHi
101 _RL fldRL(*)
102 _RS fldRS(*)
103 INTEGER jrecord
104 INTEGER myIter
105 INTEGER myThid
106 C !OUTPUT PARAMETERS:
107
108 C !FUNCTIONS
109 INTEGER ILNBLNK
110 INTEGER MDS_RECLEN
111 LOGICAL MASTER_CPU_IO
112 EXTERNAL ILNBLNK
113 EXTERNAL MDS_RECLEN
114 EXTERNAL MASTER_CPU_IO
115
116 C !LOCAL VARIABLES:
117 C bBij :: base shift in Buffer index for tile bi,bj
118 CHARACTER*(MAX_LEN_FNAM) dataFName,metaFName,pfName
119 CHARACTER*(MAX_LEN_MBUF) msgBuf
120 LOGICAL fileIsOpen
121 LOGICAL iAmDoingIO
122 LOGICAL writeMetaF
123 LOGICAL useExch2ioLayOut
124 LOGICAL zeroBuff
125 INTEGER xSize, ySize
126 INTEGER irecord
127 INTEGER iG,jG,bi,bj
128 INTEGER i1,i2,i,j,k,nNz
129 INTEGER irec,dUnit,IL,pIL
130 INTEGER dimList(3,3), nDims, map2gl(2)
131 INTEGER length_of_rec
132 INTEGER bBij
133 INTEGER tNx, tNy, global_nTx
134 INTEGER tBx, tBy, iGjLoc, jGjLoc
135 #ifdef ALLOW_EXCH2
136 INTEGER tN
137 #endif /* ALLOW_EXCH2 */
138 _RL dummyRL(1)
139 CHARACTER*8 blank8c
140
141 DATA dummyRL(1) / 0. _d 0 /
142 DATA blank8c / ' ' /
143
144 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
145 C Set dimensions:
146 xSize = Nx
147 ySize = Ny
148 useExch2ioLayOut = .FALSE.
149 #ifdef ALLOW_EXCH2
150 IF ( W2_useE2ioLayOut ) THEN
151 xSize = exch2_global_Nx
152 ySize = exch2_global_Ny
153 useExch2ioLayOut = .TRUE.
154 ENDIF
155 #endif /* ALLOW_EXCH2 */
156
157 C- default:
158 iGjLoc = 0
159 jGjLoc = 1
160
161 C Assume nothing
162 fileIsOpen = .FALSE.
163 IL = ILNBLNK( fName )
164 pIL = ILNBLNK( mdsioLocalDir )
165 nNz = 1 + kHi - kLo
166 irecord = ABS(jrecord)
167 writeMetaF = jrecord.GT.0
168
169 C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO):
170 iAmDoingIO = MASTER_CPU_IO(myThid)
171
172 C Record number must be >= 1
173 IF (irecord .LT. 1) THEN
174 WRITE(msgBuf,'(3A,I10)')
175 & ' MDS_WRITE_FIELD: file="', fName(1:IL), '" , iter=', myIter
176 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
177 & SQUEEZE_RIGHT , myThid )
178 WRITE(msgBuf,'(A,I9.8)')
179 & ' MDS_WRITE_FIELD: argument irecord = ',irecord
180 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
181 & SQUEEZE_RIGHT , myThid )
182 WRITE(msgBuf,'(A)')
183 & ' MDS_WRITE_FIELD: invalid value for irecord'
184 CALL PRINT_ERROR( msgBuf, myThid )
185 CALL ALL_PROC_DIE( myThid )
186 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
187 ENDIF
188 C check for valid sub-set of levels:
189 IF ( kLo.LT.1 .OR. kHi.GT.kSize ) THEN
190 WRITE(msgBuf,'(3A,I10)')
191 & ' MDS_WRITE_FIELD: file="', fName(1:IL), '" , iter=', myIter
192 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
193 & SQUEEZE_RIGHT , myThid )
194 WRITE(msgBuf,'(3(A,I6))')
195 & ' MDS_WRITE_FIELD: arguments kSize=', kSize,
196 & ' , kLo=', kLo, ' , kHi=', kHi
197 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
198 & SQUEEZE_RIGHT , myThid )
199 WRITE(msgBuf,'(A)')
200 & ' MDS_WRITE_FIELD: invalid sub-set of levels'
201 CALL PRINT_ERROR( msgBuf, myThid )
202 CALL ALL_PROC_DIE( myThid )
203 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
204 ENDIF
205 C check for 3-D Buffer size:
206 IF ( .NOT.useSingleCpuIO .AND. nNz.GT.size3dBuf ) THEN
207 WRITE(msgBuf,'(3A,I10)')
208 & ' MDS_WRITE_FIELD: file="', fName(1:IL), '" , iter=', myIter
209 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
210 & SQUEEZE_RIGHT , myThid )
211 WRITE(msgBuf,'(3(A,I6))')
212 & ' MDS_WRITE_FIELD: Nb Lev to write =', nNz,
213 & ' >', size3dBuf, ' = buffer 3rd Dim'
214 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
215 & SQUEEZE_RIGHT , myThid )
216 WRITE(msgBuf,'(A)')
217 & ' MDS_WRITE_FIELD: buffer 3rd Dim. too small'
218 CALL PRINT_ERROR( msgBuf, myThid )
219 WRITE(msgBuf,'(A)')
220 & ' increase "size3dBuf" in "MDSIO_BUFF_3D.h" and recompile'
221 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
222 & SQUEEZE_RIGHT , myThid)
223 CALL ALL_PROC_DIE( myThid )
224 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
225 ENDIF
226
227 C Only do I/O if I am the master thread
228 IF ( iAmDoingIO ) THEN
229
230 C Assign special directory
231 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
232 pfName = fName
233 ELSE
234 WRITE(pfName,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL)
235 ENDIF
236 pIL=ILNBLNK( pfName )
237 IF ( debugLevel .GE. debLevC ) THEN
238 WRITE(msgBuf,'(A,I8,I6,3I4,2A)')
239 & ' MDS_WRITE_FIELD: it,rec,kS,kL,kH=', myIter, jrecord,
240 & kSize, kLo, kHi, ' file=', pfName(1:pIL)
241 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
242 & SQUEEZE_RIGHT, myThid )
243 ENDIF
244
245 C Assign a free unit number as the I/O channel for this routine
246 CALL MDSFINDUNIT( dUnit, myThid )
247
248 C- endif iAmDoingIO
249 ENDIF
250
251 C If option globalFile is desired but does not work or if
252 C globalFile is too slow, then try using single-CPU I/O.
253 IF (useSingleCpuIO) THEN
254
255 C Master thread of process 0, only, opens a global file
256 IF ( iAmDoingIO ) THEN
257 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
258 length_of_rec = MDS_RECLEN( filePrec, xSize*ySize, myThid )
259 IF (irecord .EQ. 1) THEN
260 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
261 & access='direct', recl=length_of_rec )
262 ELSE
263 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
264 & access='direct', recl=length_of_rec )
265 ENDIF
266 ENDIF
267
268 C Gather array and write it to file, one vertical level at a time
269 DO k=kLo,kHi
270 zeroBuff = k.EQ.kLo
271 C- copy from fldRL/RS(level=k) to 2-D "local":
272 IF ( filePrec.EQ.precFloat32 ) THEN
273 IF ( arrType.EQ.'RS' ) THEN
274 CALL MDS_PASS_R4toRS( sharedLocBuf_r4, fldRS,
275 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
276 ELSEIF ( arrType.EQ.'RL' ) THEN
277 CALL MDS_PASS_R4toRL( sharedLocBuf_r4, fldRL,
278 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
279 ELSE
280 WRITE(msgBuf,'(2A)')
281 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
282 CALL PRINT_ERROR( msgBuf, myThid )
283 CALL ALL_PROC_DIE( myThid )
284 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
285 ENDIF
286 C Wait for all threads to finish filling shared buffer
287 CALL BAR2( myThid )
288 CALL GATHER_2D_R4(
289 O xy_buffer_r4,
290 I sharedLocBuf_r4,
291 I xSize, ySize,
292 I useExch2ioLayOut, zeroBuff, myThid )
293 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
294 IF ( arrType.EQ.'RS' ) THEN
295 CALL MDS_PASS_R8toRS( sharedLocBuf_r8, fldRS,
296 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
297 ELSEIF ( arrType.EQ.'RL' ) THEN
298 CALL MDS_PASS_R8toRL( sharedLocBuf_r8, fldRL,
299 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
300 ELSE
301 WRITE(msgBuf,'(2A)')
302 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
303 CALL PRINT_ERROR( msgBuf, myThid )
304 CALL ALL_PROC_DIE( myThid )
305 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
306 ENDIF
307 C Wait for all threads to finish filling shared buffer
308 CALL BAR2( myThid )
309 CALL GATHER_2D_R8(
310 O xy_buffer_r8,
311 I sharedLocBuf_r8,
312 I xSize, ySize,
313 I useExch2ioLayOut, zeroBuff, myThid )
314 ELSE
315 WRITE(msgBuf,'(A,I6)')
316 & ' MDS_WRITE_FIELD: illegal value for filePrec=',filePrec
317 CALL PRINT_ERROR( msgBuf, myThid )
318 CALL ALL_PROC_DIE( myThid )
319 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
320 ENDIF
321 C Make other threads wait for "gather" completion so that after this,
322 C shared buffer can again be modified by any thread
323 CALL BAR2( myThid )
324
325 IF ( iAmDoingIO ) THEN
326 irec = 1 + k-kLo + (irecord-1)*nNz
327 IF ( filePrec.EQ.precFloat32 ) THEN
328 #ifdef _BYTESWAPIO
329 CALL MDS_BYTESWAPR4( xSize*ySize, xy_buffer_r4 )
330 #endif
331 WRITE(dUnit,rec=irec) ( xy_buffer_r4(i),i=1,xSize*ySize )
332 ELSE
333 #ifdef _BYTESWAPIO
334 CALL MDS_BYTESWAPR8( xSize*ySize, xy_buffer_r8 )
335 #endif
336 WRITE(dUnit,rec=irec) ( xy_buffer_r8(i),i=1,xSize*ySize )
337 ENDIF
338 C- end if iAmDoingIO
339 ENDIF
340 C- end of k loop
341 ENDDO
342
343 C Close data-file
344 IF ( iAmDoingIO ) THEN
345 CLOSE( dUnit )
346 ENDIF
347
348 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
349 C--- else .NOT.useSingleCpuIO
350 ELSE
351
352 C Wait for all thread to finish. This prevents other threads (e.g., master)
353 C to continue to acces 3-D buffer while this thread is filling it.
354 CALL BAR2( myThid )
355
356 C--- Copy from fldRL/RS to 3-D buffer (multi-threads):
357 IF ( filePrec.EQ.precFloat32 ) THEN
358 IF ( arrType.EQ.'RS' ) THEN
359 CALL MDS_PASS_R4toRS( shared3dBuf_r4, fldRS,
360 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
361 ELSEIF ( arrType.EQ.'RL' ) THEN
362 CALL MDS_PASS_R4toRL( shared3dBuf_r4, fldRL,
363 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
364 ELSE
365 WRITE(msgBuf,'(2A)')
366 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
367 CALL PRINT_ERROR( msgBuf, myThid )
368 CALL ALL_PROC_DIE( myThid )
369 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
370 ENDIF
371 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
372 IF ( arrType.EQ.'RS' ) THEN
373 CALL MDS_PASS_R8toRS( shared3dBuf_r8, fldRS,
374 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
375 ELSEIF ( arrType.EQ.'RL' ) THEN
376 CALL MDS_PASS_R8toRL( shared3dBuf_r8, fldRL,
377 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
378 ELSE
379 WRITE(msgBuf,'(2A)')
380 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
381 CALL PRINT_ERROR( msgBuf, myThid )
382 CALL ALL_PROC_DIE( myThid )
383 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
384 ENDIF
385 ELSE
386 WRITE(msgBuf,'(A,I6)')
387 & ' MDS_WRITE_FIELD: illegal value for filePrec=',filePrec
388 CALL PRINT_ERROR( msgBuf, myThid )
389 CALL ALL_PROC_DIE( myThid )
390 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
391 ENDIF
392
393 C Wait for all threads to finish filling shared buffer
394 CALL BAR2( myThid )
395
396 C Only do I/O if I am the master thread
397 IF ( iAmDoingIO ) THEN
398
399 #ifdef _BYTESWAPIO
400 IF ( filePrec.EQ.precFloat32 ) THEN
401 CALL MDS_BYTESWAPR4( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r4 )
402 ELSE
403 CALL MDS_BYTESWAPR8( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r8 )
404 ENDIF
405 #endif
406
407 C If we are writing to a global file then we open it here
408 IF (globalFile) THEN
409 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
410 length_of_rec = MDS_RECLEN( filePrec, sNx, myThid )
411 IF (irecord .EQ. 1) THEN
412 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
413 & access='direct', recl=length_of_rec )
414 ELSE
415 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
416 & access='direct', recl=length_of_rec )
417 ENDIF
418 fileIsOpen=.TRUE.
419 ENDIF
420
421 C Loop over all tiles
422 DO bj=1,nSy
423 DO bi=1,nSx
424 bBij = sNx*sNy*nNz*( bi-1 + (bj-1)*nSx )
425
426 tNx = sNx
427 tNy = sNy
428 global_nTx = xSize/sNx
429 tBx = myXGlobalLo-1 + (bi-1)*sNx
430 tBy = myYGlobalLo-1 + (bj-1)*sNy
431 #ifdef ALLOW_EXCH2
432 IF ( useExch2ioLayOut ) THEN
433 tN = W2_myTileList(bi,bj)
434 c tNx = exch2_tNx(tN)
435 c tNy = exch2_tNy(tN)
436 c global_nTx = exch2_global_Nx/tNx
437 tBx = exch2_txGlobalo(tN) - 1
438 tBy = exch2_tyGlobalo(tN) - 1
439 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
440 C- face x-size larger than glob-size : fold it
441 iGjLoc = 0
442 jGjLoc = exch2_mydNx(tN) / xSize
443 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
444 C- tile y-size larger than glob-size : make a long line
445 iGjLoc = exch2_mydNx(tN)
446 jGjLoc = 0
447 ELSE
448 C- default (face fit into global-IO-array)
449 iGjLoc = 0
450 jGjLoc = 1
451 ENDIF
452 ENDIF
453 #endif /* ALLOW_EXCH2 */
454
455 IF (globalFile) THEN
456 C--- Case of 1 Global file:
457
458 DO k=kLo,kHi
459 DO j=1,tNy
460 irec = 1 + ( tBx + (j-1)*iGjLoc )/tNx
461 & + ( tBy + (j-1)*jGjLoc )*global_nTx
462 & +( k-kLo + (irecord-1)*nNz )*global_nTx*ySize
463 i1 = bBij + 1 + (j-1)*sNx + (k-kLo)*sNx*sNy
464 i2 = bBij + j*sNx + (k-kLo)*sNx*sNy
465 IF ( filePrec.EQ.precFloat32 ) THEN
466 WRITE(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
467 ELSE
468 WRITE(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
469 ENDIF
470 C End of j,k loops
471 ENDDO
472 ENDDO
473
474 ELSE
475 C--- Case of 1 file per tile (globalFile=F):
476
477 C If we are writing to a tiled MDS file then we open each one here
478 iG=bi+(myXGlobalLo-1)/sNx
479 jG=bj+(myYGlobalLo-1)/sNy
480 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
481 & pfName(1:pIL),'.',iG,'.',jG,'.data'
482 length_of_rec = MDS_RECLEN( filePrec, sNx*sNy*nNz, myThid )
483 IF (irecord .EQ. 1) THEN
484 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
485 & access='direct', recl=length_of_rec )
486 ELSE
487 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
488 & access='direct', recl=length_of_rec )
489 ENDIF
490 fileIsOpen=.TRUE.
491
492 irec = irecord
493 i1 = bBij + 1
494 i2 = bBij + sNx*sNy*nNz
495 IF ( filePrec.EQ.precFloat32 ) THEN
496 WRITE(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
497 ELSE
498 WRITE(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
499 ENDIF
500
501 C here We close the tiled MDS file
502 IF ( fileIsOpen ) THEN
503 CLOSE( dUnit )
504 fileIsOpen = .FALSE.
505 ENDIF
506
507 C--- End Global File / tile-file cases
508 ENDIF
509
510 C Create meta-file for each tile if we are tiling
511 IF ( .NOT.globalFile .AND. writeMetaF ) THEN
512 iG=bi+(myXGlobalLo-1)/sNx
513 jG=bj+(myYGlobalLo-1)/sNy
514 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
515 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
516 dimList(1,1) = xSize
517 dimList(2,1) = tBx + 1
518 dimList(3,1) = tBx + tNx
519 dimList(1,2) = ySize
520 dimList(2,2) = tBy + 1
521 dimList(3,2) = tBy + tNy
522 dimList(1,3) = nNz
523 dimList(2,3) = 1
524 dimList(3,3) = nNz
525 c dimList(1,3) = kSize
526 c dimList(2,3) = kLo
527 c dimList(3,3) = kHi
528 nDims = 3
529 IF ( nNz.EQ.1 ) nDims = 2
530 map2gl(1) = iGjLoc
531 map2gl(2) = jGjLoc
532 CALL MDS_WRITE_META(
533 I metaFName, dataFName, the_run_name, ' ',
534 I filePrec, nDims, dimList, map2gl, 0, blank8c,
535 I 0, dummyRL, oneRL, irecord, myIter, myThid )
536 ENDIF
537
538 C End of bi,bj loops
539 ENDDO
540 ENDDO
541
542 C If global file was opened then close it
543 IF (fileIsOpen .AND. globalFile) THEN
544 CLOSE( dUnit )
545 fileIsOpen = .FALSE.
546 ENDIF
547
548 C- endif iAmDoingIO
549 ENDIF
550
551 C Make other threads wait for I/O completion so that after this,
552 C 3-D buffer can again be modified by any thread
553 c CALL BAR2( myThid )
554
555 C if useSingleCpuIO / else / end
556 ENDIF
557
558 C Create meta-file for the global-file (also if useSingleCpuIO)
559 IF ( writeMetaF .AND. iAmDoingIO .AND.
560 & (globalFile .OR. useSingleCpuIO) ) THEN
561 WRITE(metaFName,'(2A)') fName(1:IL),'.meta'
562 dimList(1,1) = xSize
563 dimList(2,1) = 1
564 dimList(3,1) = xSize
565 dimList(1,2) = ySize
566 dimList(2,2) = 1
567 dimList(3,2) = ySize
568 dimList(1,3) = nNz
569 dimList(2,3) = 1
570 dimList(3,3) = nNz
571 c dimList(1,3) = kSize
572 c dimList(2,3) = kLo
573 c dimList(3,3) = kHi
574 nDims = 3
575 IF ( nNz.EQ.1 ) nDims = 2
576 map2gl(1) = 0
577 map2gl(2) = 1
578 CALL MDS_WRITE_META(
579 I metaFName, dataFName, the_run_name, ' ',
580 I filePrec, nDims, dimList, map2gl, 0, blank8c,
581 I 0, dummyRL, oneRL, irecord, myIter, myThid )
582 c I metaFName, dataFName, the_run_name, titleLine,
583 c I filePrec, nDims, dimList, map2gl, nFlds, fldList,
584 c I nTimRec, timList, misVal, irecord, myIter, myThid )
585 ENDIF
586
587 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
588 RETURN
589 END

  ViewVC Help
Powered by ViewVC 1.1.22