/[MITgcm]/MITgcm/pkg/mdsio/mdsio_writefield_new.F
ViewVC logotype

Annotation of /MITgcm/pkg/mdsio/mdsio_writefield_new.F

Parent Directory Parent Directory | Revision Log Revision Log | View Revision Graph Revision Graph


Revision 1.3 - (hide annotations) (download)
Fri Nov 4 01:31:36 2005 UTC (18 years, 7 months ago) by jmc
Branch: MAIN
Changes since 1.2: +3 -3 lines
remove unused variables (reduces number of compiler warning)

1 jmc 1.3 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_writefield_new.F,v 1.2 2005/11/03 16:09:32 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "MDSIO_OPTIONS.h"
5    
6     SUBROUTINE MDSWRITEFIELD_NEW(
7     I fName,
8     I filePrec,
9     I globalFile,
10     I useCurrentDir,
11     I arrType,
12     I nNzdim,nNz,
13     I arr,
14     I irecord,
15     I myIter,
16     I myThid )
17     C
18     C Arguments:
19     C
20     C fName string base name for file to written
21     C filePrec integer number of bits per word in file (32 or 64)
22     C globalFile logical selects between writing a global or tiled file
23     C useCurrentDir logical always write to the current directory (even if
24     C "mdsioLocalDir" is set)
25     C arrType char(2) declaration of "arr": either "RS" or "RL"
26     C nNzdim integer size of third dimension: normally either 1 or Nr
27     C nNz integer number of vertical levels to be written
28     C arr RS/RL array to write, arr(:,:,nNzdim,:,:)
29     C irecord integer record number to read
30     C myIter integer time step number
31     C myThid integer thread identifier
32     C
33     C MDSWRITEFIELD creates either a file of the form "fName.data" and
34     C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
35     C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
36     C "fName.xxx.yyy.meta". A meta-file is always created.
37     C Currently, the meta-files are not read because it is difficult
38     C to parse files in fortran. We should read meta information before
39     C adding records to an existing multi-record file.
40     C The precision of the file is decsribed by filePrec, set either
41     C to floatPrec32 or floatPrec64. The precision or declaration of
42     C the array argument must be consistently described by the char*(2)
43     C string arrType, either "RS" or "RL". nNz allows for both 2-D and
44     C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
45     C nNz=Nr implies a 3-D model field. irecord is the record number
46     C to be read and must be >= 1. NOTE: It is currently assumed that
47     C the highest record number in the file was the last record written.
48     C Nor is there a consistency check between the routine arguments and file.
49     C ie. if your write record 2 after record 4 the meta information
50     C will record the number of records to be 2. This, again, is because
51     C we have read the meta information. To be fixed.
52     C
53     C Created: 03/16/99 adcroft@mit.edu
54     C
55     C Changed: 05/31/00 heimbach@mit.edu
56     C open(dUnit, ..., status='old', ... -> status='unknown'
57     C
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    
63     implicit none
64     C Global variables / common blocks
65     #include "SIZE.h"
66     #include "EEPARAMS.h"
67     #include "EESUPPORT.h"
68     #include "PARAMS.h"
69     #ifdef ALLOW_EXCH2
70     #include "W2_EXCH2_TOPOLOGY.h"
71     #include "W2_EXCH2_PARAMS.h"
72     #endif /* ALLOW_EXCH2 */
73    
74     C Routine arguments
75     character*(*) fName
76     integer filePrec
77     logical globalFile
78     logical useCurrentDir
79     character*(2) arrType
80     integer nNzdim, nNz
81     cph(
82     cph Real arr(*)
83     _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNzdim,nSx,nSy)
84     cph)
85     integer irecord
86     integer myIter
87     integer myThid
88     C Functions
89     integer ILNBLNK
90     integer MDS_RECLEN
91     C Local variables
92     character*(MAX_LEN_FNAM) dataFName,metaFName,pfName
93     character*(MAX_LEN_MBUF) msgbuf
94     logical fileIsOpen
95 jmc 1.3 integer iG,jG,irec,bi,bj,j,k,dUnit,IL,pIL
96 jmc 1.1 integer dimList(3,3),ndims
97     integer x_size,y_size,length_of_rec
98     #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
99     PARAMETER ( x_size = exch2_domain_nxt * sNx )
100     PARAMETER ( y_size = exch2_domain_nyt * sNy )
101     #else
102     PARAMETER ( x_size = Nx )
103     PARAMETER ( y_size = Ny )
104     #endif
105     Real*4 r4seg(sNx)
106     Real*8 r8seg(sNx)
107     #ifdef ALLOW_USE_MPI
108 jmc 1.3 INTEGER iG_IO,jG_IO,npe,i
109 jmc 1.1 Real*4 xy_buffer_r4(x_size,y_size)
110     Real*8 xy_buffer_r8(x_size,y_size)
111     Real*8 global(Nx,Ny)
112     _RL local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
113     COMMON /GlobalLo/ mpi_myXGlobalLo, mpi_myYGlobalLo
114     INTEGER mpi_myXGlobalLo(nPx*nPy)
115     INTEGER mpi_myYGlobalLo(nPx*nPy)
116     #endif
117     #ifdef ALLOW_EXCH2
118     integer domainHeight,domainLength,tgy,tgx,tny,tnx,tn
119     #endif /* ALLOW_EXCH2 */
120    
121     C ------------------------------------------------------------------
122    
123     C Only do I/O if I am the master thread
124     _BEGIN_MASTER( myThid )
125    
126     C Record number must be >= 1
127     if (irecord .LT. 1) then
128     write(msgbuf,'(a,i9.8)')
129     & ' MDSWRITEFIELD: argument irecord = ',irecord
130     call print_message( msgbuf, standardmessageunit,
131     & SQUEEZE_RIGHT , mythid)
132     write(msgbuf,'(a)')
133     & ' MDSWRITEFIELD: invalid value for irecord'
134     call print_error( msgbuf, mythid )
135     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
136     endif
137    
138     C Assume nothing
139     fileIsOpen=.FALSE.
140     IL = ILNBLNK( fName )
141     pIL = ILNBLNK( mdsioLocalDir )
142    
143     C Assign special directory
144     IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
145     pfName = fName
146     ELSE
147     WRITE(pfName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
148     ENDIF
149     pIL=ILNBLNK( pfName )
150    
151     C Assign a free unit number as the I/O channel for this routine
152     call MDSFINDUNIT( dUnit, mythid )
153    
154     #ifdef ALLOW_USE_MPI
155     _END_MASTER( myThid )
156     C If option globalFile is desired but does not work or if
157     C globalFile is too slow, then try using single-CPU I/O.
158     if (useSingleCpuIO) then
159    
160     C Master thread of process 0, only, opens a global file
161     _BEGIN_MASTER( myThid )
162     IF( mpiMyId .EQ. 0 ) THEN
163     write(dataFName,'(2a)') fName(1:IL),'.data'
164     length_of_rec=MDS_RECLEN(filePrec,x_size*y_size,mythid)
165     if (irecord .EQ. 1) then
166     open( dUnit, file=dataFName, status=_NEW_STATUS,
167     & access='direct', recl=length_of_rec )
168     else
169     open( dUnit, file=dataFName, status=_OLD_STATUS,
170     & access='direct', recl=length_of_rec )
171     endif
172     ENDIF
173     _END_MASTER( myThid )
174    
175     C Gather array and write it to file, one vertical level at a time
176     DO k=1,nNz
177 jmc 1.2 C- copy from arr(level=k) to 2-D "local":
178     IF ( arrType.EQ.'RS' ) THEN
179     CALL MDS_PASStoRS( local, arr, k, nNzdim, .FALSE., myThid )
180     ELSEIF ( arrType.EQ.'RL' ) THEN
181     CALL MDS_PASStoRL( local, arr, k, nNzdim, .FALSE., myThid )
182     ELSE
183     WRITE(msgbuf,'(A)')
184     & ' MDSWRITEFIELD: illegal value for arrType'
185     CALL PRINT_ERROR( msgbuf, mythid )
186     STOP 'ABNORMAL END: S/R MDSWRITEFIELD'
187     ENDIF
188 jmc 1.1 CALL GATHER_2D( global, local, myThid )
189     _BEGIN_MASTER( myThid )
190     IF( mpiMyId .EQ. 0 ) THEN
191     irec=k+nNz*(irecord-1)
192     if (filePrec .eq. precFloat32) then
193     #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
194     DO J=1,y_size
195     DO I=1,x_size
196     xy_buffer_r4(I,J) = 0.0
197     ENDDO
198     ENDDO
199     bj=1
200     DO npe=1,nPx*nPy
201     DO bi=1,nSx
202     DO J=1,sNy
203     DO I=1,sNx
204     iG=mpi_myXGlobalLo(npe)-1+(bi-1)*sNx+i
205     jG=mpi_myYGlobalLo(npe)-1+(bj-1)*sNy+j
206     iG_IO=exch2_txglobalo(W2_mpi_myTileList(npe,bi))+i-1
207     jG_IO=exch2_tyglobalo(W2_mpi_myTileList(npe,bi))+j-1
208     xy_buffer_r4(iG_IO,jG_IO) = global(iG,jG)
209     ENDDO
210     ENDDO
211     ENDDO
212     ENDDO
213     #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
214     DO J=1,Ny
215     DO I=1,Nx
216     xy_buffer_r4(I,J) = global(I,J)
217     ENDDO
218     ENDDO
219     #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
220     #ifdef _BYTESWAPIO
221     call MDS_BYTESWAPR4( x_size*y_size, xy_buffer_r4 )
222     #endif
223     write(dUnit,rec=irec) xy_buffer_r4
224     elseif (filePrec .eq. precFloat64) then
225     #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
226     DO J=1,y_size
227     DO I=1,x_size
228     xy_buffer_r8(I,J) = 0.0
229     ENDDO
230     ENDDO
231     bj=1
232     DO npe=1,nPx*nPy
233     DO bi=1,nSx
234     DO J=1,sNy
235     DO I=1,sNx
236     iG=mpi_myXGlobalLo(npe)-1+(bi-1)*sNx+i
237     jG=mpi_myYGlobalLo(npe)-1+(bj-1)*sNy+j
238     iG_IO=exch2_txglobalo(W2_mpi_myTileList(npe,bi))+i-1
239     jG_IO=exch2_tyglobalo(W2_mpi_myTileList(npe,bi))+j-1
240     xy_buffer_r8(iG_IO,jG_IO) = global(iG,jG)
241     ENDDO
242     ENDDO
243     ENDDO
244     ENDDO
245     #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
246     DO J=1,Ny
247     DO I=1,Nx
248     xy_buffer_r8(I,J) = global(I,J)
249     ENDDO
250     ENDDO
251     #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
252     #ifdef _BYTESWAPIO
253     call MDS_BYTESWAPR8( x_size*y_size, xy_buffer_r8 )
254     #endif
255     write(dUnit,rec=irec) xy_buffer_r8
256     else
257     write(msgbuf,'(a)')
258     & ' MDSWRITEFIELD: illegal value for filePrec'
259     call print_error( msgbuf, mythid )
260     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
261     endif
262     ENDIF
263     _END_MASTER( myThid )
264     ENDDO
265    
266     C Close data-file and create meta-file
267     _BEGIN_MASTER( myThid )
268     IF( mpiMyId .EQ. 0 ) THEN
269     close( dUnit )
270     write(metaFName,'(2a)') fName(1:IL),'.meta'
271     dimList(1,1)=x_size
272     dimList(2,1)=1
273     dimList(3,1)=x_size
274     dimList(1,2)=y_size
275     dimList(2,2)=1
276     dimList(3,2)=y_size
277     dimList(1,3)=nNz
278     dimList(2,3)=1
279     dimList(3,3)=nNz
280     ndims=3
281     if (nNz .EQ. 1) ndims=2
282     call MDSWRITEMETA( metaFName, dataFName,
283     & filePrec, ndims, dimList, irecord, myIter, mythid )
284     ENDIF
285     _END_MASTER( myThid )
286     C To be safe, make other processes wait for I/O completion
287     _BARRIER
288    
289     elseif ( .NOT. useSingleCpuIO ) then
290     _BEGIN_MASTER( myThid )
291     #endif /* ALLOW_USE_MPI */
292    
293     C If we are writing to a global file then we open it here
294     if (globalFile) then
295     write(dataFName,'(2a)') fName(1:IL),'.data'
296     if (irecord .EQ. 1) then
297     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
298     open( dUnit, file=dataFName, status=_NEW_STATUS,
299     & access='direct', recl=length_of_rec )
300     fileIsOpen=.TRUE.
301     else
302     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
303     open( dUnit, file=dataFName, status=_OLD_STATUS,
304     & access='direct', recl=length_of_rec )
305     fileIsOpen=.TRUE.
306     endif
307     endif
308    
309     #ifdef ALLOW_EXCH2
310     if (globalFile) then
311     domainLength = exch2_domain_nxt
312     domainHeight = exch2_domain_nyt
313     C Loop over all tiles
314     do bj=1,nSy
315     do bi=1,nSx
316     tn = W2_myTileList(bi)
317     tgy = exch2_tyglobalo(tn)
318     tgx = exch2_txglobalo(tn)
319     tny = exch2_tny(tn)
320     tnx = exch2_tnx(tn)
321     if (fileIsOpen) then
322     do k=1,nNz
323     do j=1,tNy
324    
325     irec = domainLength*(tgy-1) + (tgx-1)/tnx + 1 +
326     & domainLength*(j-1) +
327     & domainLength*domainHeight*tny*(k-1) +
328     & domainLength*domainHeight*tny*nNz*(irecord-1)
329    
330    
331     if (filePrec .eq. precFloat32) then
332     if (arrType .eq. 'RS') then
333     call MDS_SEG4toRS( j,bi,bj,k,nNzdim, r4seg, .FALSE., arr )
334     elseif (arrType .eq. 'RL') then
335     call MDS_SEG4toRL( j,bi,bj,k,nNzdim, r4seg, .FALSE., arr )
336     else
337     write(msgbuf,'(a)')
338     & ' MDSWRITEFIELD: illegal value for arrType'
339     call print_error( msgbuf, mythid )
340     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
341     endif
342     #ifdef _BYTESWAPIO
343     call MDS_BYTESWAPR4( sNx, r4seg )
344     #endif
345     write(dUnit,rec=irec) r4seg
346     elseif (filePrec .eq. precFloat64) then
347     if (arrType .eq. 'RS') then
348     call MDS_SEG8toRS( j,bi,bj,k,nNzdim, r8seg, .FALSE., arr )
349     elseif (arrType .eq. 'RL') then
350     call MDS_SEG8toRL( j,bi,bj,k,nNzdim, r8seg, .FALSE., arr )
351     else
352     write(msgbuf,'(a)')
353     & ' MDSWRITEFIELD: illegal value for arrType'
354     call print_error( msgbuf, mythid )
355     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
356     endif
357     #ifdef _BYTESWAPIO
358     call MDS_BYTESWAPR8( sNx, r8seg )
359     #endif
360     write(dUnit,rec=irec) r8seg
361     else
362     write(msgbuf,'(a)')
363     & ' MDSWRITEFIELD: illegal value for filePrec'
364     call print_error( msgbuf, mythid )
365     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
366     endif
367     C End of j loop
368     enddo
369     C End of k loop
370     enddo
371     else ! .not. fileIsOpen
372     write(msgbuf,'(a)')
373     & ' MDSWRITEFIELD: I should never get to this point'
374     call print_error( msgbuf, mythid )
375     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
376     endif
377     enddo
378     enddo
379     else ! not global file
380    
381     #endif /* ALLOW_EXCH2 */
382     C Loop over all tiles
383     do bj=1,nSy
384     do bi=1,nSx
385     C If we are writing to a tiled MDS file then we open each one here
386     if (.NOT. globalFile) then
387     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
388     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
389     write(dataFName,'(2a,i3.3,a,i3.3,a)')
390     & pfName(1:pIL),'.',iG,'.',jG,'.data'
391     if (irecord .EQ. 1) then
392     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
393     open( dUnit, file=dataFName, status=_NEW_STATUS,
394     & access='direct', recl=length_of_rec )
395     fileIsOpen=.TRUE.
396     else
397     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
398     open( dUnit, file=dataFName, status=_OLD_STATUS,
399     & access='direct', recl=length_of_rec )
400     fileIsOpen=.TRUE.
401     endif
402     endif
403     if (fileIsOpen) then
404     do k=1,nNz
405     do j=1,sNy
406     if (globalFile) then
407     iG = myXGlobalLo-1+(bi-1)*sNx
408     jG = myYGlobalLo-1+(bj-1)*sNy
409     irec=1+INT(iG/sNx)+nSx*nPx*(jG+j-1)+nSx*nPx*Ny*(k-1)
410     & +nSx*nPx*Ny*nNz*(irecord-1)
411     else
412     iG = 0
413     jG = 0
414     irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
415     endif
416     if (filePrec .eq. precFloat32) then
417     if (arrType .eq. 'RS') then
418     call MDS_SEG4toRS( j,bi,bj,k,nNzdim, r4seg, .FALSE., arr )
419     elseif (arrType .eq. 'RL') then
420     call MDS_SEG4toRL( j,bi,bj,k,nNzdim, r4seg, .FALSE., arr )
421     else
422     write(msgbuf,'(a)')
423     & ' MDSWRITEFIELD: illegal value for arrType'
424     call print_error( msgbuf, mythid )
425     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
426     endif
427     #ifdef _BYTESWAPIO
428     call MDS_BYTESWAPR4( sNx, r4seg )
429     #endif
430     write(dUnit,rec=irec) r4seg
431     elseif (filePrec .eq. precFloat64) then
432     if (arrType .eq. 'RS') then
433     call MDS_SEG8toRS( j,bi,bj,k,nNzdim, r8seg, .FALSE., arr )
434     elseif (arrType .eq. 'RL') then
435     call MDS_SEG8toRL( j,bi,bj,k,nNzdim, r8seg, .FALSE., arr )
436     else
437     write(msgbuf,'(a)')
438     & ' MDSWRITEFIELD: illegal value for arrType'
439     call print_error( msgbuf, mythid )
440     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
441     endif
442     #ifdef _BYTESWAPIO
443     call MDS_BYTESWAPR8( sNx, r8seg )
444     #endif
445     write(dUnit,rec=irec) r8seg
446     else
447     write(msgbuf,'(a)')
448     & ' MDSWRITEFIELD: illegal value for filePrec'
449     call print_error( msgbuf, mythid )
450     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
451     endif
452     C End of j loop
453     enddo
454     C End of k loop
455     enddo
456     else
457     write(msgbuf,'(a)')
458     & ' MDSWRITEFIELD: I should never get to this point'
459     call print_error( msgbuf, mythid )
460     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
461     endif
462     C If we were writing to a tiled MDS file then we close it here
463     if (fileIsOpen .AND. (.NOT. globalFile)) then
464     close( dUnit )
465     fileIsOpen = .FALSE.
466     endif
467     C Create meta-file for each tile if we are tiling
468     if (.NOT. globalFile) then
469     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
470     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
471     write(metaFname,'(2a,i3.3,a,i3.3,a)')
472     & pfName(1:pIL),'.',iG,'.',jG,'.meta'
473     #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
474     tn = W2_myTileList(bi)
475     dimList(1,1)=x_size
476     dimList(2,1)=exch2_txGlobalo(tn)
477     dimList(3,1)=exch2_txGlobalo(tn)+sNx-1
478     dimList(1,2)=y_size
479     dimList(2,2)=exch2_tyGlobalo(tn)
480     dimList(3,2)=exch2_tyGlobalo(tn)+sNy-1
481     #else /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
482     C- jmc: if MISSING_TILE_IO, keep meta files unchanged
483     C to stay consistent with global file structure
484     dimList(1,1)=Nx
485     dimList(2,1)=myXGlobalLo+(bi-1)*sNx
486     dimList(3,1)=myXGlobalLo+bi*sNx-1
487     dimList(1,2)=Ny
488     dimList(2,2)=myYGlobalLo+(bj-1)*sNy
489     dimList(3,2)=myYGlobalLo+bj*sNy-1
490     #endif /* defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO) */
491     dimList(1,3)=nNz
492     dimList(2,3)=1
493     dimList(3,3)=nNz
494     ndims=3
495     if (nNz .EQ. 1) ndims=2
496     call MDSWRITEMETA( metaFName, dataFName,
497     & filePrec, ndims, dimList, irecord, myIter, mythid )
498     endif
499     C End of bi,bj loops
500     enddo
501     enddo
502     c#endif /* ALLOW_EXCH2 */
503    
504     #ifdef ALLOW_EXCH2
505     endif ! global fle
506     #endif /* ALLOW_EXCH2 */
507    
508     C If global file was opened then close it
509     if (fileIsOpen .AND. globalFile) then
510     close( dUnit )
511     fileIsOpen = .FALSE.
512     endif
513    
514     C Create meta-file for the global-file
515     if (globalFile) then
516     C We can not do this operation using threads (yet) because of the
517     C "barrier" at the next step. The barrier could be removed but
518     C at the cost of "safe" distributed I/O.
519     if (nThreads.NE.1) then
520     write(msgbuf,'(a,a)')
521     & ' MDSWRITEFIELD: A threads version of this routine',
522     & ' does not exist.'
523     call print_message( msgbuf, standardmessageunit,
524     & SQUEEZE_RIGHT , mythid)
525     write(msgbuf,'(a)')
526     & ' MDSWRITEFIELD: This needs to be fixed...'
527     call print_message( msgbuf, standardmessageunit,
528     & SQUEEZE_RIGHT , mythid)
529     write(msgbuf,'(a,i3.2)')
530     & ' MDSWRITEFIELD: nThreads = ',nThreads
531     call print_message( msgbuf, standardmessageunit,
532     & SQUEEZE_RIGHT , mythid)
533     write(msgbuf,'(a)')
534     & ' MDSWRITEFIELD: Stopping because you are using threads'
535     call print_error( msgbuf, mythid )
536     stop 'ABNORMAL END: S/R MDSWRITEFIELD'
537     endif
538     C We put a barrier here to ensure that all processes have finished
539     C writing their data before we update the meta-file
540     _BARRIER
541     write(metaFName,'(2a)') fName(1:IL),'.meta'
542     dimList(1,1)=x_size
543     dimList(2,1)=1
544     dimList(3,1)=x_size
545     dimList(1,2)=y_size
546     dimList(2,2)=1
547     dimList(3,2)=y_size
548     dimList(1,3)=nNz
549     dimList(2,3)=1
550     dimList(3,3)=nNz
551     ndims=3
552     if (nNz .EQ. 1) ndims=2
553     call MDSWRITEMETA( metaFName, dataFName,
554     & filePrec, ndims, dimList, irecord, myIter, mythid )
555     fileIsOpen=.TRUE.
556     endif
557    
558     _END_MASTER( myThid )
559    
560     #ifdef ALLOW_USE_MPI
561     C endif useSingleCpuIO
562     endif
563     #endif /* ALLOW_USE_MPI */
564    
565     C ------------------------------------------------------------------
566     return
567     end

  ViewVC Help
Powered by ViewVC 1.1.22