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

Contents of /MITgcm/pkg/mdsio/mdsio_writefield_loc.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: checkpoint54a_pre, checkpoint55c_post, checkpoint57b_post, checkpoint55d_pre, checkpoint57a_post, checkpoint55j_post, checkpoint56b_post, checkpoint54a_post, checkpoint55h_post, checkpoint54b_post, checkpoint54d_post, checkpoint56c_post, checkpoint54e_post, checkpoint55b_post, checkpoint55, checkpoint55a_post, checkpoint57c_pre, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint57, checkpoint56, checkpoint54f_post, checkpoint57c_post, checkpoint55e_post, checkpoint54c_post, checkpoint55i_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.5: +1 -2 lines
 o remove redundant #include statements

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

  ViewVC Help
Powered by ViewVC 1.1.22