/[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.17 - (show annotations) (download)
Thu Dec 23 02:41:47 2010 UTC (13 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.16: +24 -11 lines
- change arg. list of S/R MDSIO_PASS_R4/8toRL/S ;
- change barrier call for safe multi-threads access to 3-D shared buffer.

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_write_field.F,v 1.16 2009/09/01 19:08: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 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 decsribed 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
238 C Assign a free unit number as the I/O channel for this routine
239 CALL MDSFINDUNIT( dUnit, myThid )
240
241 C- endif iAmDoingIO
242 ENDIF
243
244 C If option globalFile is desired but does not work or if
245 C globalFile is too slow, then try using single-CPU I/O.
246 IF (useSingleCpuIO) THEN
247
248 C Master thread of process 0, only, opens a global file
249 IF ( iAmDoingIO ) THEN
250 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
251 length_of_rec = MDS_RECLEN( filePrec, xSize*ySize, myThid )
252 IF (irecord .EQ. 1) THEN
253 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
254 & access='direct', recl=length_of_rec )
255 ELSE
256 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
257 & access='direct', recl=length_of_rec )
258 ENDIF
259 ENDIF
260
261 C Gather array and write it to file, one vertical level at a time
262 DO k=kLo,kHi
263 zeroBuff = k.EQ.kLo
264 C- copy from fldRL/RS(level=k) to 2-D "local":
265 IF ( filePrec.EQ.precFloat32 ) THEN
266 IF ( arrType.EQ.'RS' ) THEN
267 CALL MDS_PASS_R4toRS( sharedLocBuf_r4, fldRS,
268 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
269 ELSEIF ( arrType.EQ.'RL' ) THEN
270 CALL MDS_PASS_R4toRL( sharedLocBuf_r4, fldRL,
271 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
272 ELSE
273 WRITE(msgBuf,'(2A)')
274 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
275 CALL PRINT_ERROR( msgBuf, myThid )
276 CALL ALL_PROC_DIE( myThid )
277 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
278 ENDIF
279 C Wait for all threads to finish filling shared buffer
280 CALL BAR2( myThid )
281 CALL GATHER_2D_R4(
282 O xy_buffer_r4,
283 I sharedLocBuf_r4,
284 I xSize, ySize,
285 I useExch2ioLayOut, zeroBuff, myThid )
286 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
287 IF ( arrType.EQ.'RS' ) THEN
288 CALL MDS_PASS_R8toRS( sharedLocBuf_r8, fldRS,
289 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
290 ELSEIF ( arrType.EQ.'RL' ) THEN
291 CALL MDS_PASS_R8toRL( sharedLocBuf_r8, fldRL,
292 I 0, 0, 1, k, kSize, 0, 0, .FALSE., myThid )
293 ELSE
294 WRITE(msgBuf,'(2A)')
295 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
296 CALL PRINT_ERROR( msgBuf, myThid )
297 CALL ALL_PROC_DIE( myThid )
298 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
299 ENDIF
300 C Wait for all threads to finish filling shared buffer
301 CALL BAR2( myThid )
302 CALL GATHER_2D_R8(
303 O xy_buffer_r8,
304 I sharedLocBuf_r8,
305 I xSize, ySize,
306 I useExch2ioLayOut, zeroBuff, myThid )
307 ELSE
308 WRITE(msgBuf,'(A,I6)')
309 & ' MDS_WRITE_FIELD: illegal value for filePrec=',filePrec
310 CALL PRINT_ERROR( msgBuf, myThid )
311 CALL ALL_PROC_DIE( myThid )
312 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
313 ENDIF
314 C Make other threads wait for "gather" completion so that after this,
315 C shared buffer can again be modified by any thread
316 CALL BAR2( myThid )
317
318 IF ( iAmDoingIO ) THEN
319 irec = 1 + k-kLo + (irecord-1)*nNz
320 IF ( filePrec.EQ.precFloat32 ) THEN
321 #ifdef _BYTESWAPIO
322 CALL MDS_BYTESWAPR4( xSize*ySize, xy_buffer_r4 )
323 #endif
324 WRITE(dUnit,rec=irec) ( xy_buffer_r4(i),i=1,xSize*ySize )
325 ELSE
326 #ifdef _BYTESWAPIO
327 CALL MDS_BYTESWAPR8( xSize*ySize, xy_buffer_r8 )
328 #endif
329 WRITE(dUnit,rec=irec) ( xy_buffer_r8(i),i=1,xSize*ySize )
330 ENDIF
331 C- end if iAmDoingIO
332 ENDIF
333 C- end of k loop
334 ENDDO
335
336 C Close data-file
337 IF ( iAmDoingIO ) THEN
338 CLOSE( dUnit )
339 ENDIF
340
341 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
342 C--- else .NOT.useSingleCpuIO
343 ELSE
344
345 C Wait for all thread to finish. This prevents other threads (e.g., master)
346 C to continue to acces 3-D buffer while this thread is filling it.
347 CALL BAR2( myThid )
348
349 C--- Copy from fldRL/RS to 3-D buffer (multi-threads):
350 IF ( filePrec.EQ.precFloat32 ) THEN
351 IF ( arrType.EQ.'RS' ) THEN
352 CALL MDS_PASS_R4toRS( shared3dBuf_r4, fldRS,
353 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
354 ELSEIF ( arrType.EQ.'RL' ) THEN
355 CALL MDS_PASS_R4toRL( shared3dBuf_r4, fldRL,
356 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
357 ELSE
358 WRITE(msgBuf,'(2A)')
359 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
360 CALL PRINT_ERROR( msgBuf, myThid )
361 CALL ALL_PROC_DIE( myThid )
362 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
363 ENDIF
364 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
365 IF ( arrType.EQ.'RS' ) THEN
366 CALL MDS_PASS_R8toRS( shared3dBuf_r8, fldRS,
367 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
368 ELSEIF ( arrType.EQ.'RL' ) THEN
369 CALL MDS_PASS_R8toRL( shared3dBuf_r8, fldRL,
370 I 0, 0, nNz, kLo, kSize, 0,0, .FALSE., myThid )
371 ELSE
372 WRITE(msgBuf,'(2A)')
373 & ' MDS_WRITE_FIELD: illegal value for arrType=', arrType
374 CALL PRINT_ERROR( msgBuf, myThid )
375 CALL ALL_PROC_DIE( myThid )
376 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
377 ENDIF
378 ELSE
379 WRITE(msgBuf,'(A,I6)')
380 & ' MDS_WRITE_FIELD: illegal value for filePrec=',filePrec
381 CALL PRINT_ERROR( msgBuf, myThid )
382 CALL ALL_PROC_DIE( myThid )
383 STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD'
384 ENDIF
385
386 C Wait for all threads to finish filling shared buffer
387 CALL BAR2( myThid )
388
389 C Only do I/O if I am the master thread
390 IF ( iAmDoingIO ) THEN
391
392 #ifdef _BYTESWAPIO
393 IF ( filePrec.EQ.precFloat32 ) THEN
394 CALL MDS_BYTESWAPR4( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r4 )
395 ELSE
396 CALL MDS_BYTESWAPR8( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r8 )
397 ENDIF
398 #endif
399
400 C If we are writing to a global file then we open it here
401 IF (globalFile) THEN
402 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
403 length_of_rec = MDS_RECLEN( filePrec, sNx, myThid )
404 IF (irecord .EQ. 1) THEN
405 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
406 & access='direct', recl=length_of_rec )
407 ELSE
408 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
409 & access='direct', recl=length_of_rec )
410 ENDIF
411 fileIsOpen=.TRUE.
412 ENDIF
413
414 C Loop over all tiles
415 DO bj=1,nSy
416 DO bi=1,nSx
417 bBij = sNx*sNy*nNz*( bi-1 + (bj-1)*nSx )
418
419 tNx = sNx
420 tNy = sNy
421 global_nTx = xSize/sNx
422 tBx = myXGlobalLo-1 + (bi-1)*sNx
423 tBy = myYGlobalLo-1 + (bj-1)*sNy
424 #ifdef ALLOW_EXCH2
425 IF ( useExch2ioLayOut ) THEN
426 tN = W2_myTileList(bi,bj)
427 c tNx = exch2_tNx(tN)
428 c tNy = exch2_tNy(tN)
429 c global_nTx = exch2_global_Nx/tNx
430 tBx = exch2_txGlobalo(tN) - 1
431 tBy = exch2_tyGlobalo(tN) - 1
432 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
433 C- face x-size larger than glob-size : fold it
434 iGjLoc = 0
435 jGjLoc = exch2_mydNx(tN) / xSize
436 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
437 C- tile y-size larger than glob-size : make a long line
438 iGjLoc = exch2_mydNx(tN)
439 jGjLoc = 0
440 ELSE
441 C- default (face fit into global-IO-array)
442 iGjLoc = 0
443 jGjLoc = 1
444 ENDIF
445 ENDIF
446 #endif /* ALLOW_EXCH2 */
447
448 IF (globalFile) THEN
449 C--- Case of 1 Global file:
450
451 DO k=kLo,kHi
452 DO j=1,tNy
453 irec = 1 + ( tBx + (j-1)*iGjLoc )/tNx
454 & + ( tBy + (j-1)*jGjLoc )*global_nTx
455 & +( k-kLo + (irecord-1)*nNz )*global_nTx*ySize
456 i1 = bBij + 1 + (j-1)*sNx + (k-kLo)*sNx*sNy
457 i2 = bBij + j*sNx + (k-kLo)*sNx*sNy
458 IF ( filePrec.EQ.precFloat32 ) THEN
459 WRITE(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
460 ELSE
461 WRITE(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
462 ENDIF
463 C End of j,k loops
464 ENDDO
465 ENDDO
466
467 ELSE
468 C--- Case of 1 file per tile (globalFile=F):
469
470 C If we are writing to a tiled MDS file then we open each one here
471 iG=bi+(myXGlobalLo-1)/sNx
472 jG=bj+(myYGlobalLo-1)/sNy
473 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
474 & pfName(1:pIL),'.',iG,'.',jG,'.data'
475 length_of_rec = MDS_RECLEN( filePrec, sNx*sNy*nNz, myThid )
476 IF (irecord .EQ. 1) THEN
477 OPEN( dUnit, file=dataFName, status=_NEW_STATUS,
478 & access='direct', recl=length_of_rec )
479 ELSE
480 OPEN( dUnit, file=dataFName, status=_OLD_STATUS,
481 & access='direct', recl=length_of_rec )
482 ENDIF
483 fileIsOpen=.TRUE.
484
485 irec = irecord
486 i1 = bBij + 1
487 i2 = bBij + sNx*sNy*nNz
488 IF ( filePrec.EQ.precFloat32 ) THEN
489 WRITE(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
490 ELSE
491 WRITE(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
492 ENDIF
493
494 C here We close the tiled MDS file
495 IF ( fileIsOpen ) THEN
496 CLOSE( dUnit )
497 fileIsOpen = .FALSE.
498 ENDIF
499
500 C--- End Global File / tile-file cases
501 ENDIF
502
503 C Create meta-file for each tile if we are tiling
504 IF ( .NOT.globalFile .AND. writeMetaF ) THEN
505 iG=bi+(myXGlobalLo-1)/sNx
506 jG=bj+(myYGlobalLo-1)/sNy
507 WRITE(metaFname,'(2A,I3.3,A,I3.3,A)')
508 & pfName(1:pIL),'.',iG,'.',jG,'.meta'
509 dimList(1,1) = xSize
510 dimList(2,1) = tBx + 1
511 dimList(3,1) = tBx + tNx
512 dimList(1,2) = ySize
513 dimList(2,2) = tBy + 1
514 dimList(3,2) = tBy + tNy
515 dimList(1,3) = nNz
516 dimList(2,3) = 1
517 dimList(3,3) = nNz
518 c dimList(1,3) = kSize
519 c dimList(2,3) = kLo
520 c dimList(3,3) = kHi
521 nDims = 3
522 IF ( nNz.EQ.1 ) nDims = 2
523 map2gl(1) = iGjLoc
524 map2gl(2) = jGjLoc
525 CALL MDS_WRITE_META(
526 I metaFName, dataFName, the_run_name, ' ',
527 I filePrec, nDims, dimList, map2gl, 0, blank8c,
528 I 0, dummyRL, irecord, myIter, myThid )
529 ENDIF
530
531 C End of bi,bj loops
532 ENDDO
533 ENDDO
534
535 C If global file was opened then close it
536 IF (fileIsOpen .AND. globalFile) THEN
537 CLOSE( dUnit )
538 fileIsOpen = .FALSE.
539 ENDIF
540
541 C- endif iAmDoingIO
542 ENDIF
543
544 C Make other threads wait for I/O completion so that after this,
545 C 3-D buffer can again be modified by any thread
546 c CALL BAR2( myThid )
547
548 C if useSingleCpuIO / else / end
549 ENDIF
550
551 C Create meta-file for the global-file (also if useSingleCpuIO)
552 IF ( writeMetaF .AND. iAmDoingIO .AND.
553 & (globalFile .OR. useSingleCpuIO) ) THEN
554 WRITE(metaFName,'(2A)') fName(1:IL),'.meta'
555 dimList(1,1) = xSize
556 dimList(2,1) = 1
557 dimList(3,1) = xSize
558 dimList(1,2) = ySize
559 dimList(2,2) = 1
560 dimList(3,2) = ySize
561 dimList(1,3) = nNz
562 dimList(2,3) = 1
563 dimList(3,3) = nNz
564 c dimList(1,3) = kSize
565 c dimList(2,3) = kLo
566 c dimList(3,3) = kHi
567 nDims = 3
568 IF ( nNz.EQ.1 ) nDims = 2
569 map2gl(1) = 0
570 map2gl(2) = 1
571 CALL MDS_WRITE_META(
572 I metaFName, dataFName, the_run_name, ' ',
573 I filePrec, nDims, dimList, map2gl, 0, blank8c,
574 I 0, dummyRL, irecord, myIter, myThid )
575 c I metaFName, dataFName, the_run_name, titleLine,
576 c I filePrec, nDims, dimList, map2gl, nFlds, fldList,
577 c I nTimRec, timList, irecord, myIter, myThid )
578 ENDIF
579
580 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
581 RETURN
582 END

  ViewVC Help
Powered by ViewVC 1.1.22