1 |
C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writefield_new.F,v 1.6 2005/11/08 15:53:41 cnh 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 your 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 |
110 |
INTEGER x_size,y_size,length_of_rec |
111 |
#if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) |
112 |
INTEGER iG_IO,jG_IO,npe |
113 |
PARAMETER ( x_size = exch2_domain_nxt * sNx ) |
114 |
PARAMETER ( y_size = exch2_domain_nyt * sNy ) |
115 |
#else |
116 |
PARAMETER ( x_size = Nx ) |
117 |
PARAMETER ( y_size = Ny ) |
118 |
#endif |
119 |
Real*4 r4seg(sNx) |
120 |
Real*8 r8seg(sNx) |
121 |
Real*4 xy_buffer_r4(x_size,y_size) |
122 |
Real*8 xy_buffer_r8(x_size,y_size) |
123 |
Real*8 globalBuf(Nx,Ny) |
124 |
#ifdef ALLOW_EXCH2 |
125 |
c INTEGER tGy,tGx,tNy,tNx,tn |
126 |
INTEGER tGy,tGx, tNx,tn |
127 |
#endif /* ALLOW_EXCH2 */ |
128 |
INTEGER tNy |
129 |
|
130 |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
131 |
|
132 |
C Assume nothing |
133 |
fileIsOpen = .FALSE. |
134 |
IL = ILNBLNK( fName ) |
135 |
pIL = ILNBLNK( mdsioLocalDir ) |
136 |
irecord = ABS(jrecord) |
137 |
writeMetaF = jrecord.GT.0 |
138 |
|
139 |
C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO): |
140 |
iAmDoingIO = MASTER_CPU_IO(myThid) |
141 |
|
142 |
C Only do I/O if I am the master thread |
143 |
IF ( iAmDoingIO ) THEN |
144 |
|
145 |
C Record number must be >= 1 |
146 |
IF (irecord .LT. 1) THEN |
147 |
WRITE(msgBuf,'(A,I9.8)') |
148 |
& ' MDS_WRITE_FIELD: argument irecord = ',irecord |
149 |
CALL PRINT_MESSAGE( msgBuf, standardMessageUnit, |
150 |
& SQUEEZE_RIGHT , myThid) |
151 |
WRITE(msgBuf,'(A)') |
152 |
& ' MDS_WRITE_FIELD: invalid value for irecord' |
153 |
CALL PRINT_ERROR( msgBuf, myThid ) |
154 |
STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD' |
155 |
ENDIF |
156 |
|
157 |
C Assign special directory |
158 |
IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN |
159 |
pfName = fName |
160 |
ELSE |
161 |
WRITE(pfName,'(2A)') mdsioLocalDir(1:pIL), fName(1:IL) |
162 |
ENDIF |
163 |
pIL=ILNBLNK( pfName ) |
164 |
|
165 |
C Assign a free unit number as the I/O channel for this routine |
166 |
CALL MDSFINDUNIT( dUnit, myThid ) |
167 |
|
168 |
C- endif iAmDoingIO |
169 |
ENDIF |
170 |
|
171 |
C If option globalFile is desired but does not work or if |
172 |
C globalFile is too slow, then try using single-CPU I/O. |
173 |
IF (useSingleCpuIO) THEN |
174 |
|
175 |
C Master thread of process 0, only, opens a global file |
176 |
IF ( iAmDoingIO ) THEN |
177 |
WRITE(dataFName,'(2a)') fName(1:IL),'.data' |
178 |
length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,myThid) |
179 |
IF (irecord .EQ. 1) THEN |
180 |
OPEN( dUnit, file=dataFName, status=_NEW_STATUS, |
181 |
& access='direct', recl=length_of_rec ) |
182 |
ELSE |
183 |
OPEN( dUnit, file=dataFName, status=_OLD_STATUS, |
184 |
& access='direct', recl=length_of_rec ) |
185 |
ENDIF |
186 |
ENDIF |
187 |
|
188 |
C Gather array and WRITE it to file, one vertical level at a time |
189 |
DO k=1,nNz |
190 |
C- copy from arr(level=k) to 2-D "local": |
191 |
IF ( arrType.EQ.'RS' ) THEN |
192 |
CALL MDS_PASStoRS(sharedLocalBuf,arr,k,zSize,.FALSE.,myThid) |
193 |
ELSEIF ( arrType.EQ.'RL' ) THEN |
194 |
CALL MDS_PASStoRL(sharedLocalBuf,arr,k,zSize,.FALSE.,myThid) |
195 |
ELSE |
196 |
WRITE(msgBuf,'(A)') |
197 |
& ' MDS_WRITE_FIELD: illegal value for arrType' |
198 |
CALL PRINT_ERROR( msgBuf, myThid ) |
199 |
STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD' |
200 |
ENDIF |
201 |
CALL GATHER_2D( globalBuf, sharedLocalBuf, myThid ) |
202 |
|
203 |
IF ( iAmDoingIO ) THEN |
204 |
irec=k+nNz*(irecord-1) |
205 |
IF (filePrec .EQ. precFloat32) THEN |
206 |
#if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) |
207 |
DO J=1,y_size |
208 |
DO I=1,x_size |
209 |
xy_buffer_r4(I,J) = 0.0 |
210 |
ENDDO |
211 |
ENDDO |
212 |
bj=1 |
213 |
DO npe=1,nPx*nPy |
214 |
DO bi=1,nSx |
215 |
DO J=1,sNy |
216 |
DO I=1,sNx |
217 |
#ifdef ALLOW_USE_MPI |
218 |
iG=mpi_myXGlobalLo(npe)-1+(bi-1)*sNx+i |
219 |
jG=mpi_myYGlobalLo(npe)-1+(bj-1)*sNy+j |
220 |
#else |
221 |
iG= myXGlobalLo-1+(bi-1)*sNx+i |
222 |
jG= myYGlobalLo-1+(bj-1)*sNy+j |
223 |
#endif /* ALLOW_USE_MPI */ |
224 |
iG_IO=exch2_txGlobalo(W2_mpi_myTileList(npe,bi))+i-1 |
225 |
jG_IO=exch2_tyGlobalo(W2_mpi_myTileList(npe,bi))+j-1 |
226 |
xy_buffer_r4(iG_IO,jG_IO) = globalBuf(iG,jG) |
227 |
ENDDO |
228 |
ENDDO |
229 |
ENDDO |
230 |
ENDDO |
231 |
#else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */ |
232 |
DO J=1,Ny |
233 |
DO I=1,Nx |
234 |
xy_buffer_r4(I,J) = globalBuf(I,J) |
235 |
ENDDO |
236 |
ENDDO |
237 |
#endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */ |
238 |
#ifdef _BYTESWAPIO |
239 |
CALL MDS_BYTESWAPR4( x_size*y_size, xy_buffer_r4 ) |
240 |
#endif |
241 |
WRITE(dUnit,rec=irec) xy_buffer_r4 |
242 |
ELSEIF (filePrec .EQ. precFloat64) THEN |
243 |
#if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) |
244 |
DO J=1,y_size |
245 |
DO I=1,x_size |
246 |
xy_buffer_r8(I,J) = 0.0 |
247 |
ENDDO |
248 |
ENDDO |
249 |
bj=1 |
250 |
DO npe=1,nPx*nPy |
251 |
DO bi=1,nSx |
252 |
DO J=1,sNy |
253 |
DO I=1,sNx |
254 |
#ifdef ALLOW_USE_MPI |
255 |
iG=mpi_myXGlobalLo(npe)-1+(bi-1)*sNx+i |
256 |
jG=mpi_myYGlobalLo(npe)-1+(bj-1)*sNy+j |
257 |
#else |
258 |
iG= myXGlobalLo-1+(bi-1)*sNx+i |
259 |
jG= myYGlobalLo-1+(bj-1)*sNy+j |
260 |
#endif /* ALLOW_USE_MPI */ |
261 |
iG_IO=exch2_txGlobalo(W2_mpi_myTileList(npe,bi))+i-1 |
262 |
jG_IO=exch2_tyGlobalo(W2_mpi_myTileList(npe,bi))+j-1 |
263 |
xy_buffer_r8(iG_IO,jG_IO) = globalBuf(iG,jG) |
264 |
ENDDO |
265 |
ENDDO |
266 |
ENDDO |
267 |
ENDDO |
268 |
#else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */ |
269 |
DO J=1,Ny |
270 |
DO I=1,Nx |
271 |
xy_buffer_r8(I,J) = globalBuf(I,J) |
272 |
ENDDO |
273 |
ENDDO |
274 |
#endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */ |
275 |
#ifdef _BYTESWAPIO |
276 |
CALL MDS_BYTESWAPR8( x_size*y_size, xy_buffer_r8 ) |
277 |
#endif |
278 |
WRITE(dUnit,rec=irec) xy_buffer_r8 |
279 |
ELSE |
280 |
WRITE(msgBuf,'(A)') |
281 |
& ' MDS_WRITE_FIELD: illegal value for filePrec' |
282 |
CALL PRINT_ERROR( msgBuf, myThid ) |
283 |
STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD' |
284 |
ENDIF |
285 |
ENDIF |
286 |
ENDDO |
287 |
|
288 |
C Close data-file |
289 |
IF ( iAmDoingIO ) THEN |
290 |
CLOSE( dUnit ) |
291 |
ENDIF |
292 |
|
293 |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
294 |
C--- else .NOT.useSingleCpuIO |
295 |
ELSE |
296 |
|
297 |
C Only do I/O if I am the master thread |
298 |
IF ( iAmDoingIO ) THEN |
299 |
|
300 |
C If we are writing to a global file then we open it here |
301 |
IF (globalFile) THEN |
302 |
WRITE(dataFName,'(2a)') fName(1:IL),'.data' |
303 |
IF (irecord .EQ. 1) THEN |
304 |
length_of_rec=MDS_RECLEN( filePrec, sNx, myThid ) |
305 |
OPEN( dUnit, file=dataFName, status=_NEW_STATUS, |
306 |
& access='direct', recl=length_of_rec ) |
307 |
fileIsOpen=.TRUE. |
308 |
ELSE |
309 |
length_of_rec=MDS_RECLEN( filePrec, sNx, myThid ) |
310 |
OPEN( dUnit, file=dataFName, status=_OLD_STATUS, |
311 |
& access='direct', recl=length_of_rec ) |
312 |
fileIsOpen=.TRUE. |
313 |
ENDIF |
314 |
ENDIF |
315 |
|
316 |
C Loop over all tiles |
317 |
DO bj=1,nSy |
318 |
DO bi=1,nSx |
319 |
C If we are writing to a tiled MDS file then we open each one here |
320 |
IF (.NOT. globalFile) THEN |
321 |
iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles |
322 |
jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles |
323 |
WRITE(dataFName,'(2A,I3.3,A,I3.3,A)') |
324 |
& pfName(1:pIL),'.',iG,'.',jG,'.data' |
325 |
IF (irecord .EQ. 1) THEN |
326 |
length_of_rec=MDS_RECLEN( filePrec, sNx, myThid ) |
327 |
OPEN( dUnit, file=dataFName, status=_NEW_STATUS, |
328 |
& access='direct', recl=length_of_rec ) |
329 |
fileIsOpen=.TRUE. |
330 |
ELSE |
331 |
length_of_rec=MDS_RECLEN( filePrec, sNx, myThid ) |
332 |
OPEN( dUnit, file=dataFName, status=_OLD_STATUS, |
333 |
& access='direct', recl=length_of_rec ) |
334 |
fileIsOpen=.TRUE. |
335 |
ENDIF |
336 |
ENDIF |
337 |
IF (fileIsOpen) THEN |
338 |
tNy = sNy |
339 |
#ifdef ALLOW_EXCH2 |
340 |
tn = W2_myTileList(bi) |
341 |
tGy = exch2_tyGlobalo(tn) |
342 |
tGx = exch2_txGlobalo(tn) |
343 |
tNy = exch2_tNy(tn) |
344 |
tNx = exch2_tNx(tn) |
345 |
#endif /* ALLOW_EXCH2 */ |
346 |
DO k=1,nNz |
347 |
DO j=1,tNy |
348 |
IF (globalFile) THEN |
349 |
#ifdef ALLOW_EXCH2 |
350 |
irec = 1 + (tGx-1)/tNx |
351 |
& + ( j-1 + tGy-1 )*exch2_domain_nxt |
352 |
& + ( k-1 + (irecord-1)*nNz |
353 |
& )*tNy*exch2_domain_nyt*exch2_domain_nxt |
354 |
#else /* ALLOW_EXCH2 */ |
355 |
iG = myXGlobalLo-1 + (bi-1)*sNx |
356 |
jG = myYGlobalLo-1 + (bj-1)*sNy |
357 |
irec= 1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) |
358 |
& + nSx*nPx*Ny*(k-1) |
359 |
& + nSx*nPx*Ny*nNz*(irecord-1) |
360 |
#endif /* ALLOW_EXCH2 */ |
361 |
ELSE |
362 |
iG = 0 |
363 |
jG = 0 |
364 |
irec=j + sNy*(k-1) + sNy*nNz*(irecord-1) |
365 |
ENDIF |
366 |
IF (filePrec .EQ. precFloat32) THEN |
367 |
IF (arrType .EQ. 'RS') THEN |
368 |
CALL MDS_SEG4toRS( j,bi,bj,k,zSize, r4seg,.FALSE.,arr ) |
369 |
ELSEIF (arrType .EQ. 'RL') THEN |
370 |
CALL MDS_SEG4toRL( j,bi,bj,k,zSize, r4seg,.FALSE.,arr ) |
371 |
ELSE |
372 |
WRITE(msgBuf,'(A)') |
373 |
& ' MDS_WRITE_FIELD: illegal value for arrType' |
374 |
CALL PRINT_ERROR( msgBuf, myThid ) |
375 |
STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD' |
376 |
ENDIF |
377 |
#ifdef _BYTESWAPIO |
378 |
CALL MDS_BYTESWAPR4( sNx, r4seg ) |
379 |
#endif |
380 |
WRITE(dUnit,rec=irec) r4seg |
381 |
ELSEIF (filePrec .EQ. precFloat64) THEN |
382 |
IF (arrType .EQ. 'RS') THEN |
383 |
CALL MDS_SEG8toRS( j,bi,bj,k,zSize, r8seg,.FALSE.,arr ) |
384 |
ELSEIF (arrType .EQ. 'RL') THEN |
385 |
CALL MDS_SEG8toRL( j,bi,bj,k,zSize, r8seg,.FALSE.,arr ) |
386 |
ELSE |
387 |
WRITE(msgBuf,'(A)') |
388 |
& ' MDS_WRITE_FIELD: illegal value for arrType' |
389 |
CALL PRINT_ERROR( msgBuf, myThid ) |
390 |
STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD' |
391 |
ENDIF |
392 |
#ifdef _BYTESWAPIO |
393 |
CALL MDS_BYTESWAPR8( sNx, r8seg ) |
394 |
#endif |
395 |
WRITE(dUnit,rec=irec) r8seg |
396 |
ELSE |
397 |
WRITE(msgBuf,'(A)') |
398 |
& ' MDS_WRITE_FIELD: illegal value for filePrec' |
399 |
CALL PRINT_ERROR( msgBuf, myThid ) |
400 |
STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD' |
401 |
ENDIF |
402 |
C End of j loop |
403 |
ENDDO |
404 |
C End of k loop |
405 |
ENDDO |
406 |
ELSE |
407 |
C fileIsOpen=F |
408 |
WRITE(msgBuf,'(A)') |
409 |
& ' MDS_WRITE_FIELD: I should never get to this point' |
410 |
CALL PRINT_ERROR( msgBuf, myThid ) |
411 |
STOP 'ABNORMAL END: S/R MDS_WRITE_FIELD' |
412 |
ENDIF |
413 |
C If we were writing to a tiled MDS file then we close it here |
414 |
IF (fileIsOpen .AND. (.NOT. globalFile)) THEN |
415 |
CLOSE( dUnit ) |
416 |
fileIsOpen = .FALSE. |
417 |
ENDIF |
418 |
C Create meta-file for each tile if we are tiling |
419 |
IF ( .NOT.globalFile .AND. writeMetaF ) THEN |
420 |
iG=bi+(myXGlobalLo-1)/sNx |
421 |
jG=bj+(myYGlobalLo-1)/sNy |
422 |
WRITE(metaFname,'(2A,I3.3,A,I3.3,A)') |
423 |
& pfName(1:pIL),'.',iG,'.',jG,'.meta' |
424 |
#if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) |
425 |
tn = W2_myTileList(bi) |
426 |
dimList(1,1)=x_size |
427 |
dimList(2,1)=exch2_txGlobalo(tn) |
428 |
dimList(3,1)=exch2_txGlobalo(tn)+sNx-1 |
429 |
dimList(1,2)=y_size |
430 |
dimList(2,2)=exch2_tyGlobalo(tn) |
431 |
dimList(3,2)=exch2_tyGlobalo(tn)+sNy-1 |
432 |
#else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */ |
433 |
C- jmc: if MISSING_TILE_IO, keep meta files unchanged |
434 |
C to stay consistent with global file structure |
435 |
dimList(1,1)=Nx |
436 |
dimList(2,1)=myXGlobalLo+(bi-1)*sNx |
437 |
dimList(3,1)=myXGlobalLo+bi*sNx-1 |
438 |
dimList(1,2)=Ny |
439 |
dimList(2,2)=myYGlobalLo+(bj-1)*sNy |
440 |
dimList(3,2)=myYGlobalLo+bj*sNy-1 |
441 |
#endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */ |
442 |
dimList(1,3)=nNz |
443 |
dimList(2,3)=1 |
444 |
dimList(3,3)=nNz |
445 |
nDims=3 |
446 |
IF ( nNz.EQ.1 ) nDims=2 |
447 |
CALL MDS_WRITE_META( |
448 |
I metaFName, dataFName, the_run_name, ' ', |
449 |
I filePrec, nDims, dimList, 0, ' ', |
450 |
I 0, UNSET_RL, irecord, myIter, myThid ) |
451 |
ENDIF |
452 |
C End of bi,bj loops |
453 |
ENDDO |
454 |
ENDDO |
455 |
|
456 |
C If global file was opened then close it |
457 |
IF (fileIsOpen .AND. globalFile) THEN |
458 |
CLOSE( dUnit ) |
459 |
fileIsOpen = .FALSE. |
460 |
ENDIF |
461 |
|
462 |
C- endif iAmDoingIO |
463 |
ENDIF |
464 |
|
465 |
C if useSingleCpuIO / else / end |
466 |
ENDIF |
467 |
|
468 |
C Create meta-file for the global-file (also if useSingleCpuIO) |
469 |
IF ( writeMetaF .AND. iAmDoingIO .AND. |
470 |
& (globalFile .OR. useSingleCpuIO) ) THEN |
471 |
WRITE(metaFName,'(2A)') fName(1:IL),'.meta' |
472 |
dimList(1,1)=x_size |
473 |
dimList(2,1)=1 |
474 |
dimList(3,1)=x_size |
475 |
dimList(1,2)=y_size |
476 |
dimList(2,2)=1 |
477 |
dimList(3,2)=y_size |
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 |
CALL MDS_WRITE_META( |
484 |
I metaFName, dataFName, the_run_name, ' ', |
485 |
I filePrec, nDims, dimList, 0, ' ', |
486 |
I 0, UNSET_RL, irecord, myIter, myThid ) |
487 |
c I metaFName, dataFName, the_run_name, titleLine, |
488 |
c I filePrec, nDims, dimList, nFlds, fldList, |
489 |
c I nTimRec, timList, irecord, myIter, myThid ) |
490 |
ENDIF |
491 |
|
492 |
C To be safe, make other processes wait for I/O completion |
493 |
_BARRIER |
494 |
|
495 |
C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----| |
496 |
RETURN |
497 |
END |