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

Contents of /MITgcm/pkg/mdsio/mdswritefield_new.F

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


Revision 1.6 - (show annotations) (download)
Mon Jul 5 20:25:47 2004 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint54f_post, checkpoint56b_post, checkpoint56, checkpoint55g_post, checkpoint55j_post, checkpoint55c_post, checkpoint55f_post, checkpoint57c_post, checkpoint54a_post, checkpoint55e_post, checkpoint57a_pre, checkpoint57, checkpoint54b_post, checkpoint55h_post, checkpoint54a_pre, checkpoint54c_post, checkpoint54d_post, checkpoint56c_post, checkpoint54e_post, checkpoint57b_post, checkpoint55b_post, checkpoint55i_post, checkpoint55d_pre, checkpoint55, checkpoint55a_post, checkpoint57a_post, checkpoint56a_post, checkpoint57c_pre, checkpoint55d_post
Changes since 1.5: +1 -2 lines
 o remove redundant #include statements

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

  ViewVC Help
Powered by ViewVC 1.1.22