/[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.20 - (show annotations) (download)
Tue Aug 12 17:38:11 2014 UTC (9 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: 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, checkpoint65c, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.19: +28 -9 lines
stop if file-name (+prefix) is too long (e.g., > MAX_LEN_MBUF - 90 )

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

  ViewVC Help
Powered by ViewVC 1.1.22