/[MITgcm]/MITgcm/eesupp/src/mdsio.F
ViewVC logotype

Contents of /MITgcm/eesupp/src/mdsio.F

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


Revision 1.3 - (show annotations) (download)
Mon May 17 14:40:36 1999 UTC (25 years ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint22, checkpoint23, checkpoint21
Changes since 1.2: +8 -3 lines
Ooops: Tile numbers for meta-fiels weren't right under MPI.

1 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/mdsio.F,v 1.2 1999/05/07 18:14:16 adcroft Exp $
2
3 #include "CPP_OPTIONS.h"
4
5 C The three "public" routines supplied here are:
6 C
7 C MDSREADFIELD - read model field from direct access global or tiled MDS file
8 C MDSWRITEFIELD - write model field to direct access global or tiled MDS file
9 C MDSFINDUNIT - returns an available (unused) I/O channel
10 C MDSREADVECTOR - read vector from direct access global or tiled MDS file
11 C MDSWRITEVECTOR- write vector to direct access global or tiled MDS file
12 C
13 C all other routines are "private" to these utilities and ought
14 C not be accessed directly from the main code.
15 C
16 C Created: 03/16/99 adcroft@mit.edu
17 C Modified: 03/23/99 adcroft@mit.edu
18 C To work with multiple records
19 C Modified: 03/29/99 eckert@mit.edu
20 C Added arbitrary vector capability
21 C
22
23 #undef SAFE_IO
24
25 #ifdef SAFE_IO
26 #define _NEW_STATUS 'new'
27 #else
28 #define _NEW_STATUS 'unknown'
29 #endif
30
31 C=======================================================================
32 SUBROUTINE MDSREADFIELD(
33 I fName,
34 I filePrec,
35 I arrType,
36 I nNz,
37 O arr,
38 I irecord,
39 I myThid )
40 C
41 C Arguments:
42 C
43 C fName string base name for file to read
44 C filePrec integer number of bits per word in file (32 or 64)
45 C arrType char(2) declaration of "arr": either "RS" or "RL"
46 C nNz integer size of third dimension: normally either 1 or Nr
47 C arr RS/RL array to read into, arr(:,:,nNz,:,:)
48 C irecord integer record number to read
49 C myThid integer thread identifier
50 C
51 C MDSREADFIELD first checks to see if the file "fName" exists, then
52 C if the file "fName.data" exists and finally the tiled files of the
53 C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
54 C read because it is difficult to parse files in fortran.
55 C The precision of the file is decsribed by filePrec, set either
56 C to floatPrec32 or floatPrec64. The precision or declaration of
57 C the array argument must be consistently described by the char*(2)
58 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
59 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
60 C nNz=Nr implies a 3-D model field. irecord is the record number
61 C to be read and must be >= 1. The file data is stored in
62 C arr *but* the overlaps are *not* updated. ie. An exchange must
63 C be called. This is because the routine is sometimes called from
64 C within a MASTER_THID region.
65 C
66 C Created: 03/16/99 adcroft@mit.edu
67
68 implicit none
69 C Global variables / common blocks
70 #include "SIZE.h"
71 #include "EEPARAMS.h"
72 #include "PARAMS.h"
73
74 C Routine arguments
75 character*(*) fName
76 integer filePrec
77 character*(2) arrType
78 integer nNz
79 Real arr(*)
80 integer irecord
81 integer myThid
82 C Functions
83 integer ILNBLNK
84 integer MDS_RECLEN
85 C Local variables
86 character*(80) dataFName
87 integer iG,jG,irec,bi,bj,j,k,dUnit,IL
88 logical exst
89 Real*4 r4seg(sNx)
90 Real*8 r8seg(sNx)
91 logical globalFile,fileIsOpen
92 integer length_of_rec
93 C ------------------------------------------------------------------
94
95 C Only do I/O if I am the master thread
96 _BEGIN_MASTER( myThid )
97
98 C Record number must be >= 1
99 if (irecord .LT. 1) then
100 write(0,'(a,i)') 'MDSREADFIELD: argument irecord = ',irecord
101 stop 'MDSREADFIELD: *ERROR* Invalid value for irecord'
102 endif
103
104 C Assume nothing
105 globalFile = .FALSE.
106 fileIsOpen = .FALSE.
107 IL=ILNBLNK( fName )
108
109 C Assign a free unit number as the I/O channel for this routine
110 call MDSFINDUNIT( dUnit )
111
112 C Check first for global file with simple name (ie. fName)
113 dataFName = fName
114 inquire( file=dataFname, exist=exst )
115 if (exst) then
116 write(0,'(2a)') 'MDSREADFIELD: opening global file: ',dataFName
117 globalFile = .TRUE.
118 endif
119
120 C If negative check for global file with MDS name (ie. fName.data)
121 if (.NOT. globalFile) then
122 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
123 inquire( file=dataFname, exist=exst )
124 if (exst) then
125 write(0,'(2a)') 'MDSREADFIELD: opening global file: ',dataFName
126 globalFile = .TRUE.
127 endif
128 endif
129
130 C If we are reading from a global file then we open it here
131 if (globalFile) then
132 length_of_rec=MDS_RECLEN( filePrec, sNx )
133 open( dUnit, file=dataFName, status='old',
134 & access='direct', recl=length_of_rec )
135 fileIsOpen=.TRUE.
136 endif
137
138 C Loop over all tiles
139 do bj=1,nSy
140 do bi=1,nSx
141 C If we are reading from a tiled MDS file then we open each one here
142 if (.NOT. globalFile) then
143 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
144 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
145 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
146 & fName(1:IL),'.',iG,'.',jG,'.data'
147 inquire( file=dataFname, exist=exst )
148 C Of course, we only open the file if the tile is "active"
149 C (This is a place-holder for the active/passive mechanism
150 if (exst) then
151 write(0,'(2a)') 'MDSREADFIELD: opening file: ',dataFName
152 length_of_rec=MDS_RECLEN( filePrec, sNx )
153 open( dUnit, file=dataFName, status='old',
154 & access='direct', recl=length_of_rec )
155 fileIsOpen=.TRUE.
156 else
157 fileIsOpen=.FALSE.
158 write(0,*) 'MDSREADFIELD: filename=',dataFName
159 stop 'MDSREADFIELD: File does not exist'
160 C stop 'MDSREADFIELD: un-active tiles not implemented yet'
161 endif
162 endif
163
164 if (fileIsOpen) then
165 do k=1,nNz
166 do j=1,sNy
167 if (globalFile) then
168 iG = myXGlobalLo-1 + (bi-1)*sNx
169 jG = myYGlobalLo-1 + (bj-1)*sNy
170 irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
171 & + nSx*nPx*Ny*nNz*(irecord-1)
172 else
173 iG = 0
174 jG = 0
175 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
176 endif
177 if (filePrec .eq. precFloat32) then
178 read(dUnit,rec=irec) r4seg
179 #ifdef _BYTESWAPIO
180 call MDS_BYTESWAPR4( sNx, r4seg )
181 #endif
182 if (arrType .eq. 'RS') then
183 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
184 elseif (arrType .eq. 'RL') then
185 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
186 else
187 stop 'MDSREADFIELD: illegal value for arrType'
188 endif
189 elseif (filePrec .eq. precFloat64) then
190 read(dUnit,rec=irec) r8seg
191 #ifdef _BYTESWAPIO
192 call MDS_BYTESWAPR8( sNx, r8seg )
193 #endif
194 if (arrType .eq. 'RS') then
195 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
196 elseif (arrType .eq. 'RL') then
197 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
198 else
199 stop 'MDSREADFIELD: illegal value for arrType'
200 endif
201 else
202 stop 'MDSREADFIELD: illegal value for filePrec'
203 endif
204 C End of j loop
205 enddo
206 C End of k loop
207 enddo
208 if (.NOT. globalFile) then
209 close( dUnit )
210 fileIsOpen = .FALSE.
211 endif
212 endif
213 C End of bi,bj loops
214 enddo
215 enddo
216
217 C If global file was opened then close it
218 if (fileIsOpen .AND. globalFile) then
219 close( dUnit )
220 fileIsOpen = .FALSE.
221 endif
222
223 _END_MASTER( myThid )
224
225 C ------------------------------------------------------------------
226 return
227 end
228 C=======================================================================
229
230 C=======================================================================
231 SUBROUTINE MDSWRITEFIELD(
232 I fName,
233 I filePrec,
234 I globalFile,
235 I arrType,
236 I nNz,
237 I arr,
238 I irecord,
239 I myIter,
240 I myThid )
241 C
242 C Arguments:
243 C
244 C fName string base name for file to written
245 C filePrec integer number of bits per word in file (32 or 64)
246 C globalFile logical selects between writing a global or tiled file
247 C arrType char(2) declaration of "arr": either "RS" or "RL"
248 C nNz integer size of third dimension: normally either 1 or Nr
249 C arr RS/RL array to write, arr(:,:,nNz,:,:)
250 C irecord integer record number to read
251 C myIter integer time step number
252 C myThid integer thread identifier
253 C
254 C MDSWRITEFIELD creates either a file of the form "fName.data" and
255 C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
256 C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
257 C "fName.xxx.yyy.meta". A meta-file is always created.
258 C Currently, the meta-files are not read because it is difficult
259 C to parse files in fortran. We should read meta information before
260 C adding records to an existing multi-record file.
261 C The precision of the file is decsribed by filePrec, set either
262 C to floatPrec32 or floatPrec64. The precision or declaration of
263 C the array argument must be consistently described by the char*(2)
264 C string arrType, either "RS" or "RL". nNz allows for both 2-D and
265 C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
266 C nNz=Nr implies a 3-D model field. irecord is the record number
267 C to be read and must be >= 1. NOTE: It is currently assumed that
268 C the highest record number in the file was the last record written.
269 C Nor is there a consistency check between the routine arguments and file.
270 C ie. if your write record 2 after record 4 the meta information
271 C will record the number of records to be 2. This, again, is because
272 C we have read the meta information. To be fixed.
273 C
274 C Created: 03/16/99 adcroft@mit.edu
275
276 implicit none
277 C Global variables / common blocks
278 #include "SIZE.h"
279 #include "EEPARAMS.h"
280 #include "PARAMS.h"
281
282 C Routine arguments
283 character*(*) fName
284 integer filePrec
285 logical globalFile
286 character*(2) arrType
287 integer nNz
288 Real arr(*)
289 integer irecord
290 integer myIter
291 integer myThid
292 C Functions
293 integer ILNBLNK
294 integer MDS_RECLEN
295 C Local variables
296 character*(80) dataFName,metaFName
297 integer iG,jG,irec,bi,bj,j,k,dUnit,IL
298 Real*4 r4seg(sNx)
299 Real*8 r8seg(sNx)
300 integer dimList(3,3),ndims
301 integer length_of_rec
302 logical fileIsOpen
303 C ------------------------------------------------------------------
304
305 C Only do I/O if I am the master thread
306 _BEGIN_MASTER( myThid )
307
308 C Record number must be >= 1
309 if (irecord .LT. 1) then
310 write(0,'(a,i)') 'MDSWRITEFIELD: argument irecord = ',irecord
311 stop 'MDSWRITEFIELD: *ERROR* Invalid value for irecord'
312 endif
313
314 C Assume nothing
315 fileIsOpen=.FALSE.
316 IL=ILNBLNK( fName )
317
318 C Assign a free unit number as the I/O channel for this routine
319 call MDSFINDUNIT( dUnit )
320
321 C If we are writing to a global file then we open it here
322 if (globalFile) then
323 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
324 if (irecord .EQ. 1) then
325 length_of_rec=MDS_RECLEN( filePrec, sNx )
326 open( dUnit, file=dataFName, status=_NEW_STATUS,
327 & access='direct', recl=length_of_rec )
328 fileIsOpen=.TRUE.
329 else
330 length_of_rec=MDS_RECLEN( filePrec, sNx )
331 open( dUnit, file=dataFName, status='old',
332 & access='direct', recl=length_of_rec )
333 fileIsOpen=.TRUE.
334 endif
335 endif
336
337 C Loop over all tiles
338 do bj=1,nSy
339 do bi=1,nSx
340 C If we are writing to a tiled MDS file then we open each one here
341 if (.NOT. globalFile) then
342 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
343 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
344 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
345 & fName(1:IL),'.',iG,'.',jG,'.data'
346 if (irecord .EQ. 1) then
347 length_of_rec=MDS_RECLEN( filePrec, sNx )
348 open( dUnit, file=dataFName, status=_NEW_STATUS,
349 & access='direct', recl=length_of_rec )
350 fileIsOpen=.TRUE.
351 else
352 length_of_rec=MDS_RECLEN( filePrec, sNx )
353 open( dUnit, file=dataFName, status='old',
354 & access='direct', recl=length_of_rec )
355 fileIsOpen=.TRUE.
356 endif
357 endif
358 if (fileIsOpen) then
359 do k=1,nNz
360 do j=1,sNy
361 if (globalFile) then
362 iG = myXGlobalLo-1+(bi-1)*sNx
363 jG = myYGlobalLo-1+(bj-1)*sNy
364 irec=1+INT(iG/sNx)+nSx*nPx*(jG+j-1)+nSx*nPx*Ny*(k-1)
365 & +nSx*nPx*Ny*nNz*(irecord-1)
366 else
367 iG = 0
368 jG = 0
369 irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
370 endif
371 if (filePrec .eq. precFloat32) then
372 if (arrType .eq. 'RS') then
373 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
374 elseif (arrType .eq. 'RL') then
375 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
376 else
377 stop 'MDSWRITEFIELD: illegal value for arrType'
378 endif
379 #ifdef _BYTESWAPIO
380 call MDS_BYTESWAPR4( sNx, r4seg )
381 #endif
382 write(dUnit,rec=irec) r4seg
383 elseif (filePrec .eq. precFloat64) then
384 if (arrType .eq. 'RS') then
385 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
386 elseif (arrType .eq. 'RL') then
387 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
388 else
389 stop 'MDSWRITEFIELD: illegal value for arrType'
390 endif
391 #ifdef _BYTESWAPIO
392 call MDS_BYTESWAPR8( sNx, r8seg )
393 #endif
394 write(dUnit,rec=irec) r8seg
395 else
396 stop 'MDSWRITEFIELD: illegal value for filePrec'
397 endif
398 C End of j loop
399 enddo
400 C End of k loop
401 enddo
402 else
403 stop 'MDSWRITEFIELD: I should not ever get to this point'
404 endif
405 C If we were writing to a tiled MDS file then we close it here
406 if (fileIsOpen .AND. (.NOT. globalFile)) then
407 close( dUnit )
408 fileIsOpen = .FALSE.
409 endif
410 C Create meta-file for each tile if we are tiling
411 if (.NOT. globalFile) then
412 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
413 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
414 write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
415 & fName(1:IL),'.',iG,'.',jG,'.meta'
416 dimList(1,1)=Nx
417 dimList(2,1)=myXGlobalLo+(bi-1)*sNx
418 dimList(3,1)=myXGlobalLo+bi*sNx-1
419 dimList(1,2)=Ny
420 dimList(2,2)=myYGlobalLo+(bj-1)*sNy
421 dimList(3,2)=myYGlobalLo+bj*sNy-1
422 dimList(1,3)=Nr
423 dimList(2,3)=1
424 dimList(3,3)=Nr
425 ndims=3
426 if (nNz .EQ. 1) ndims=2
427 call MDSWRITEMETA( metaFName, dataFName,
428 & filePrec, ndims, dimList, irecord, myIter )
429 endif
430 C End of bi,bj loops
431 enddo
432 enddo
433
434 C If global file was opened then close it
435 if (fileIsOpen .AND. globalFile) then
436 close( dUnit )
437 fileIsOpen = .FALSE.
438 endif
439
440 C Create meta-file for the global-file
441 if (globalFile) then
442 C We can't do this operation using threads (yet) because of the
443 C "barrier" at the next step. The barrier could be removed but
444 C at the cost of "safe" distributed I/O.
445 if (nThreads.NE.1) then
446 write(0,*)
447 & 'MDSWRITEFIELD: A threads version of this routine does not exist'
448 write(0,*) 'MDSWRITEFIELD: This needs to be fixed...'
449 write(0,*) 'MDSWRITEFIELD: nThreads = ',nThreads
450 stop 'MDSWRITEFIELD: Stopping because you are using threads'
451 endif
452 C We put a barrier here to ensure that all processes have finished
453 C writing their data before we update the meta-file
454 _BARRIER
455 write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
456 dimList(1,1)=Nx
457 dimList(2,1)=1
458 dimList(3,1)=Nx
459 dimList(1,2)=Ny
460 dimList(2,2)=1
461 dimList(3,2)=Ny
462 dimList(1,3)=Nr
463 dimList(2,3)=1
464 dimList(3,3)=Nr
465 ndims=3
466 if (nNz .EQ. 1) ndims=2
467 call MDSWRITEMETA( metaFName, dataFName,
468 & filePrec, ndims, dimList, irecord, myIter )
469 fileIsOpen=.TRUE.
470 endif
471
472 _END_MASTER( myThid )
473
474 C ------------------------------------------------------------------
475 return
476 end
477 C=======================================================================
478
479 C=======================================================================
480 subroutine MDS_SEG4toRS( j,bi,bj,k,nNz, seg, copyTo, arr )
481 C IN:
482 C j,bi,bj,k integer - indices to array "arr"
483 C nNz integer - K dimension of array "arr"
484 C seg Real*4 - 1-D vector of length sNx
485 C OUT:
486 C arr _RS - model tiled array
487 C
488 C Created: 03/20/99 adcroft@mit.edu
489
490 implicit none
491 C Global variables / common blocks
492 #include "SIZE.h"
493
494 C Arguments
495 integer j,bi,bj,k,nNz
496 _RS arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
497 logical copyTo
498 Real*4 seg(sNx)
499 C Local
500 integer ii
501
502 C ------------------------------------------------------------------
503
504 if (copyTo) then
505 do ii=1,sNx
506 arr(ii,j,k,bi,bj)=seg(ii)
507 enddo
508 else
509 do ii=1,sNx
510 seg(ii)=arr(ii,j,k,bi,bj)
511 enddo
512 endif
513
514 C ------------------------------------------------------------------
515 return
516 end
517 C=======================================================================
518
519 C=======================================================================
520 subroutine MDS_SEG4toRL( j,bi,bj,k,nNz, seg, copyTo, arr )
521 C IN:
522 C j,bi,bj,k integer - indices to array "arr"
523 C nNz integer - K dimension of array "arr"
524 C seg Real*4 - 1-D vector of length sNx
525 C OUT:
526 C arr _RL - model tiled array
527 C
528 C Created: 03/20/99 adcroft@mit.edu
529
530 implicit none
531 C Global variables / common blocks
532 #include "SIZE.h"
533
534 C Arguments
535 integer j,bi,bj,k,nNz
536 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
537 logical copyTo
538 Real*4 seg(sNx)
539 C Local
540 integer ii
541 C ------------------------------------------------------------------
542 if (copyTo) then
543 do ii=1,sNx
544 arr(ii,j,k,bi,bj)=seg(ii)
545 enddo
546 else
547 do ii=1,sNx
548 seg(ii)=arr(ii,j,k,bi,bj)
549 enddo
550 endif
551 C ------------------------------------------------------------------
552 return
553 end
554 C=======================================================================
555
556 C=======================================================================
557 subroutine MDS_SEG8toRS( j,bi,bj,k,nNz, seg, copyTo, arr )
558 C IN:
559 C j,bi,bj,k integer - indices to array "arr"
560 C nNz integer - K dimension of array "arr"
561 C seg Real*8 - 1-D vector of length sNx
562 C OUT:
563 C arr _RS - model tiled array
564 C
565 C Created: 03/20/99 adcroft@mit.edu
566
567 implicit none
568 C Global variables / common blocks
569 #include "SIZE.h"
570
571 C Arguments
572 integer j,bi,bj,k,nNz
573 _RS arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
574 logical copyTo
575 Real*8 seg(sNx)
576 C Local
577 integer ii
578 C ------------------------------------------------------------------
579 if (copyTo) then
580 do ii=1,sNx
581 arr(ii,j,k,bi,bj)=seg(ii)
582 enddo
583 else
584 do ii=1,sNx
585 seg(ii)=arr(ii,j,k,bi,bj)
586 enddo
587 endif
588 C ------------------------------------------------------------------
589 return
590 end
591 C=======================================================================
592
593 C=======================================================================
594 subroutine MDS_SEG8toRL( j,bi,bj,k,nNz, seg, copyTo, arr )
595 C IN:
596 C j,bi,bj,k integer - indices to array "arr"
597 C nNz integer - K dimension of array "arr"
598 C seg Real*8 - 1-D vector of length sNx
599 C OUT:
600 C arr _RL - model tiled array
601 C
602 C Created: 03/20/99 adcroft@mit.edu
603
604 implicit none
605 C Global variables / common blocks
606 #include "SIZE.h"
607
608 C Arguments
609 integer j,bi,bj,k,nNz
610 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
611 logical copyTo
612 Real*8 seg(sNx)
613 C Local
614 integer ii
615 C ------------------------------------------------------------------
616 if (copyTo) then
617 do ii=1,sNx
618 arr(ii,j,k,bi,bj)=seg(ii)
619 enddo
620 else
621 do ii=1,sNx
622 seg(ii)=arr(ii,j,k,bi,bj)
623 enddo
624 endif
625 C ------------------------------------------------------------------
626 return
627 end
628 C=======================================================================
629
630 C=======================================================================
631 subroutine MDSWRITEMETA(
632 I mFileName,
633 I dFileName,
634 I filePrec,
635 I ndims,
636 I dimList,
637 I nrecords,
638 I myIter )
639
640 C IN:
641 C mFileName string - complete name of meta-file
642 C dFileName string - complete name of data-file
643 C ndims integer - number of dimensions
644 C dimList integer - array of dimensions, etc.
645 C nrecords integer - record number
646 C myIter integer - time-step number
647 C OUT:
648 C
649 C Created: 03/20/99 adcroft@mit.edu
650
651 implicit none
652 C Arguments
653 character*(*) mFileName
654 character*(*) dFileName
655 integer filePrec
656 integer ndims
657 integer dimList(3,ndims)
658 integer nrecords
659 integer myIter
660
661 C Global variables / common blocks
662 #include "SIZE.h"
663 #include "EEPARAMS.h"
664 #include "PARAMS.h"
665
666 C Functions
667 integer ILNBLNK
668 C Local
669 integer i,ii,mUnit
670 logical ex
671 C ------------------------------------------------------------------
672
673 C We should *read* the met-file if it exists to check
674 C that the information we are writing is consistent
675 C with the current contents
676 inquire( file=mFileName, exist=ex )
677 C However, it is bloody difficult to parse files
678 C in fortran so someone else can do this.
679 C For now, we will assume everything is ok
680 C and that the last record is written to the
681 C last consecutive record in the file.
682
683 C Assign a free unit number as the I/O channel for this subroutine
684 call MDSFINDUNIT( mUnit )
685
686 C Open meta-file
687 open( mUnit, file=mFileName, status='unknown',
688 & form='formatted' )
689
690 C Write the number of dimensions
691 write(mUnit,'(x,a,i3,a)') 'nDims = [ ',ndims,' ];'
692
693 C For each dimension, write the following:
694 C 1 global size (ie. the size of the global dimension of all files)
695 C 2 global start (ie. the global position of the start of this file)
696 C 3 global end (ie. the global position of the end of this file)
697
698 write(mUnit,'(x,a)') 'dimList = ['
699 do ii=1,ndims
700 if (ii.lt.ndims) then
701 write(mUnit,'(10x,3(i5,","))') (dimList(i,ii),i=1,3)
702 else
703 write(mUnit,'(10x,i5,",",i5,",",i5)') (dimList(i,ii),i=1,3)
704 endif
705 enddo
706 write(mUnit,'(10x,a)') '];'
707
708 C Record the precision of the file
709 if (filePrec .EQ. precFloat32) then
710 write(mUnit,'(x,a)') "format = [ 'float32' ];"
711 elseif (filePrec .EQ. precFloat64) then
712 write(mUnit,'(x,a)') "format = [ 'float64' ];"
713 else
714 stop 'MDSWRITEMETA: invalid filePrec'
715 endif
716
717 C Record the current record number
718 C This is a proxy for the actual number of records in the file.
719 C If we could read the file then we could do this properly.
720 write(mUnit,'(x,a,i5,a)') 'nrecords = [ ',nrecords,' ];'
721
722 C Record the file-name for the binary data
723 Cveto ii=ILNBLNK( dFileName )
724 Cveto write(mUnit,'(x,3a)') 'binarydatafile = [ ',dFileName(1:ii),' ];'
725
726 C Write the integer time (integer iteration number) for later record
727 C keeping. If the timestep number is less than 0 then we assume
728 C that the information is superfluous and do not write it.
729 if (myIter .ge. 0)
730 & write(mUnit,'(x,a,i8,a)') 'timeStepNumber = [ ',myIter,' ];'
731
732 C Close meta-file
733 close(mUnit)
734
735 C ------------------------------------------------------------------
736 return
737 end
738 C=======================================================================
739
740 C=======================================================================
741 subroutine MDSFINDUNIT( iounit )
742 C OUT:
743 C iounit integer - unit number
744 C
745 C MDSFINDUNIT returns a valid, unused unit number for f77 I/O
746 C The routine stops the program is an error occurs in the process
747 C of searching the I/O channels.
748 C
749 C Created: 03/20/99 adcroft@mit.edu
750
751 implicit none
752 C Arguments
753 integer iounit
754 C Local
755 integer ii
756 logical op
757 integer ios
758 C ------------------------------------------------------------------
759
760 C Sweep through a valid range of unit numbers
761 iounit=-1
762 do ii=9,99
763 if (iounit.eq.-1) then
764 inquire(unit=ii,iostat=ios,opened=op)
765 if (ios.ne.0) then
766 write(0,*) 'MDSFINDUNIT: inquiring unit number =',ii
767 stop 'MDSFINDUNIT: inquire statement failed!'
768 endif
769 if (.NOT. op) then
770 iounit=ii
771 endif
772 endif
773 enddo
774
775 C Was there an available unit number
776 if (iounit.eq.-1) then
777 stop 'MDSFINDUNIT: could not find an available unit number!'
778 endif
779
780 C ------------------------------------------------------------------
781 return
782 end
783 C=======================================================================
784
785 C=======================================================================
786 integer function MDS_RECLEN( filePrec, nnn )
787 C IN:
788 C filePrec integer - precision of file in bits
789 C nnn integer - number of elements in record
790 C OUT:
791 C MDS_RECLEN integer - appropriate length of record in bytes or words
792 C
793 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
794
795 implicit none
796 C Arguments
797 integer filePrec
798 integer nnn
799 C Global variables
800 #include "SIZE.h"
801 #include "EEPARAMS.h"
802 #include "PARAMS.h"
803 C Local
804 C ------------------------------------------------------------------
805
806 if (filePrec .EQ. precFloat32) then
807 MDS_RECLEN=nnn*WORDLENGTH
808 elseif (filePrec .EQ. precFloat64) then
809 MDS_RECLEN=nnn*WORDLENGTH*2
810 else
811 write(0,*) 'MDS_RECLEN: filePrec = ',filePrec
812 stop 'MDS_RECLEN: Illegal value for filePrec'
813 endif
814
815 C ------------------------------------------------------------------
816 return
817 end
818 C=======================================================================
819
820 C=======================================================================
821 SUBROUTINE MDSREADVECTOR(
822 I fName,
823 I filePrec,
824 I arrType,
825 I narr,
826 O arr,
827 I irecord,
828 I myThid )
829 C
830 C Arguments:
831 C
832 C fName string base name for file to read
833 C filePrec integer number of bits per word in file (32 or 64)
834 C arrType char(2) declaration of "arr": either "RS" or "RL"
835 C narr integer size of third dimension: normally either 1 or Nr
836 C arr RS/RL array to read into, arr(narr)
837 C irecord integer record number to read
838 C myThid integer thread identifier
839 C
840 C Created: 03/26/99 eckert@mit.edu
841 C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
842 C Fixed to work work with _RS and _RL declarations
843
844 implicit none
845 C Global variables / common blocks
846 #include "SIZE.h"
847 #include "EEPARAMS.h"
848 #include "PARAMS.h"
849
850 C Routine arguments
851 character*(*) fName
852 integer filePrec
853 character*(2) arrType
854 integer narr
855 Real arr(narr)
856 integer irecord
857 integer myThid
858 C Functions
859 integer ILNBLNK
860 integer MDS_RECLEN
861 C Local variables
862 character*(80) dataFName
863 integer iG,jG,irec,bi,bj,dUnit,IL
864 logical exst
865 logical globalFile,fileIsOpen
866 integer length_of_rec
867 C ------------------------------------------------------------------
868
869 C Only do I/O if I am the master thread
870 _BEGIN_MASTER( myThid )
871
872 C Record number must be >= 1
873 if (irecord .LT. 1) then
874 write(0,'(a,i)') 'MDSREADVECTOR: argument irecord = ',irecord
875 stop 'MDSREADVECTOR: *ERROR* Invalid value for irecord'
876 endif
877
878 C Assume nothing
879 globalFile = .FALSE.
880 fileIsOpen = .FALSE.
881 IL=ILNBLNK( fName )
882
883 C Assign a free unit number as the I/O channel for this routine
884 call MDSFINDUNIT( dUnit )
885
886 C Check first for global file with simple name (ie. fName)
887 dataFName = fName
888 inquire( file=dataFname, exist=exst )
889 if (exst) then
890 write(0,'(2a)') 'MDSREADVECTOR: opening global file: ',dataFName
891 globalFile = .TRUE.
892 endif
893
894 C If negative check for global file with MDS name (ie. fName.data)
895 if (.NOT. globalFile) then
896 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
897 inquire( file=dataFname, exist=exst )
898 if (exst) then
899 write(0,'(2a)') 'MDSREADVECTOR: opening global file: ',dataFName
900 globalFile = .TRUE.
901 endif
902 endif
903
904 C If we are reading from a global file then we open it here
905 if (globalFile) then
906 length_of_rec=MDS_RECLEN( filePrec, narr )
907 open( dUnit, file=dataFName, status='old',
908 & access='direct', recl=length_of_rec )
909 fileIsOpen=.TRUE.
910 endif
911
912 C Loop over all tiles
913 do bj=1,nSy
914 do bi=1,nSx
915 C If we are reading from a tiled MDS file then we open each one here
916 if (.NOT. globalFile) then
917 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
918 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
919 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
920 & fName(1:IL),'.',iG,'.',jG,'.data'
921 inquire( file=dataFname, exist=exst )
922 C Of course, we only open the file if the tile is "active"
923 C (This is a place-holder for the active/passive mechanism)
924 if (exst) then
925 write(0,'(2a)') 'MDSREADVECTOR: opening file: ',dataFName
926 length_of_rec=MDS_RECLEN( filePrec, narr )
927 open( dUnit, file=dataFName, status='old',
928 & access='direct', recl=length_of_rec )
929 fileIsOpen=.TRUE.
930 else
931 fileIsOpen=.FALSE.
932 stop 'MDSREADVECTOR: un-active tiles not implemented yet'
933 endif
934 endif
935 if (fileIsOpen) then
936 if (globalFile) then
937 iG = myXGlobalLo-1+(bi-1)*sNx
938 jG = myYGlobalLo-1+(bj-1)*sNy
939 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
940 & (irecord-1)*nSx*nPx*nSy*nPy
941 else
942 iG = 0
943 jG = 0
944 irec = irecord
945 endif
946 if (filePrec .eq. precFloat32) then
947 call MDS_READ_RS_VEC( dUnit, irec, narr, arr )
948 elseif (filePrec .eq. precFloat64) then
949 call MDS_READ_RL_VEC( dUnit, irec, narr, arr )
950 else
951 stop 'MDSREADVECTOR: illegal value for filePrec'
952 endif
953 if (.NOT. globalFile) then
954 close( dUnit )
955 fileIsOpen = .FALSE.
956 endif
957 endif
958 C End of bi,bj loops
959 enddo
960 enddo
961
962 C If global file was opened then close it
963 if (fileIsOpen .AND. globalFile) then
964 close( dUnit )
965 fileIsOpen = .FALSE.
966 endif
967
968 _END_MASTER( myThid )
969
970 C ------------------------------------------------------------------
971 return
972 end
973 C=======================================================================
974
975 C=======================================================================
976 SUBROUTINE MDSWRITEVECTOR(
977 I fName,
978 I filePrec,
979 I globalfile,
980 I arrType,
981 I narr,
982 I arr,
983 I irecord,
984 I myIter,
985 I myThid )
986 C Arguments:
987 C
988 C fName string base name for file to written
989 C filePrec integer number of bits per word in file (32 or 64)
990 C globalFile logical selects between writing a global or tiled file
991 C arrType char(2) declaration of "arr": either "RS" or "RL"
992 C narr integer size of third dimension: normally either 1 or Nr
993 C arr RS/RL array to write, arr(narr)
994 C irecord integer record number to read
995 C myIter integer time step number
996 C myThid integer thread identifier
997 C
998 C Created: 03/26/99 eckert@mit.edu
999 C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
1000 C Fixed to work work with _RS and _RL declarations
1001
1002 implicit none
1003 C Global variables / common blocks
1004 #include "SIZE.h"
1005 #include "EEPARAMS.h"
1006 #include "PARAMS.h"
1007
1008 C Routine arguments
1009 character*(*) fName
1010 integer filePrec
1011 logical globalfile
1012 character*(2) arrType
1013 integer narr
1014 Real arr(narr)
1015 integer irecord
1016 integer myIter
1017 integer myThid
1018 C Functions
1019 integer ILNBLNK
1020 integer MDS_RECLEN
1021 C Local variables
1022 character*(80) dataFName,metaFName
1023 integer iG,jG,irec,bi,bj,dUnit,IL
1024 logical fileIsOpen
1025 integer dimList(3,3),ndims
1026 integer length_of_rec
1027 C ------------------------------------------------------------------
1028
1029 C Only do I/O if I am the master thread
1030 _BEGIN_MASTER( myThid )
1031
1032 C Record number must be >= 1
1033 if (irecord .LT. 1) then
1034 write(0,'(a,i)') 'MDSWRITEVECTOR: argument irecord = ',irecord
1035 stop 'MDSWRITEVECTOR: *ERROR* Invalid value for irecord'
1036 endif
1037
1038 C Assume nothing
1039 fileIsOpen = .FALSE.
1040 IL=ILNBLNK( fName )
1041
1042 C Assign a free unit number as the I/O channel for this routine
1043 call MDSFINDUNIT( dUnit )
1044
1045 C If we are writing to a global file then we open it here
1046 if (globalFile) then
1047 write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
1048 if (irecord .EQ. 1) then
1049 length_of_rec = MDS_RECLEN( filePrec, narr )
1050 open( dUnit, file=dataFName, status=_NEW_STATUS,
1051 & access='direct', recl=length_of_rec )
1052 fileIsOpen=.TRUE.
1053 else
1054 length_of_rec = MDS_RECLEN( filePrec, narr )
1055 open( dUnit, file=dataFName, status='old',
1056 & access='direct', recl=length_of_rec )
1057 fileIsOpen=.TRUE.
1058 endif
1059 endif
1060
1061 C Loop over all tiles
1062 do bj=1,nSy
1063 do bi=1,nSx
1064 C If we are writing to a tiled MDS file then we open each one here
1065 if (.NOT. globalFile) then
1066 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
1067 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
1068 write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
1069 & fName(1:IL),'.',iG,'.',jG,'.data'
1070 if (irecord .EQ. 1) then
1071 length_of_rec = MDS_RECLEN( filePrec, narr )
1072 open( dUnit, file=dataFName, status=_NEW_STATUS,
1073 & access='direct', recl=length_of_rec )
1074 fileIsOpen=.TRUE.
1075 else
1076 length_of_rec = MDS_RECLEN( filePrec, narr )
1077 open( dUnit, file=dataFName, status='old',
1078 & access='direct', recl=length_of_rec )
1079 fileIsOpen=.TRUE.
1080 endif
1081 endif
1082 if (fileIsOpen) then
1083 if (globalFile) then
1084 iG = myXGlobalLo-1+(bi-1)*sNx
1085 jG = myYGlobalLo-1+(bj-1)*sNy
1086 irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
1087 & (irecord-1)*nSx*nPx*nSy*nPy
1088 else
1089 iG = 0
1090 jG = 0
1091 irec = irecord
1092 endif
1093 if (filePrec .eq. precFloat32) then
1094 call MDS_WRITE_RS_VEC( dUnit, irec, narr, arr )
1095 elseif (filePrec .eq. precFloat64) then
1096 call MDS_WRITE_RL_VEC( dUnit, irec, narr, arr )
1097 else
1098 stop 'MDSWRITEVECTOR: illegal value for filePrec'
1099 endif
1100 else
1101 stop 'MDSWRITEVECTOR: I should not ever get to this point'
1102 endif
1103 C If we were writing to a tiled MDS file then we close it here
1104 if (fileIsOpen .AND. (.NOT. globalFile)) then
1105 close( dUnit )
1106 fileIsOpen = .FALSE.
1107 endif
1108 C Create meta-file for each tile file
1109 if (.NOT. globalFile) then
1110 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
1111 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
1112 write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
1113 & fName(1:IL),'.',iG,'.',jG,'.meta'
1114 dimList(1,1) = nPx*nSx*narr
1115 dimList(2,1) = (int(myXGlobalLo/sNx)+(bi-1))*narr
1116 dimList(3,1) = (int(myXGlobalLo/sNx)+ bi )*narr - 1
1117 dimList(1,2) = nPy*nSy
1118 dimList(2,2) = int(myYGlobalLo/sNy) + bj - 1
1119 dimList(3,2) = int(myYGlobalLo/sNy) + bj - 1
1120 dimList(1,3) = 1
1121 dimList(2,3) = 1
1122 dimList(3,3) = 1
1123 ndims=1
1124 call MDSWRITEMETA( metaFName, dataFName,
1125 & filePrec, ndims, dimList, irecord, myIter )
1126 endif
1127 C End of bi,bj loops
1128 enddo
1129 enddo
1130
1131 C If global file was opened then close it
1132 if (fileIsOpen .AND. globalFile) then
1133 close( dUnit )
1134 fileIsOpen = .FALSE.
1135 endif
1136
1137 C Create meta-file for global file
1138 if (globalFile) then
1139 write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
1140 dimList(1,1) = nPx*nSx*narr
1141 dimList(2,1) = 1
1142 dimList(3,1) = nPx*nSx*narr
1143 dimList(1,2) = nPy*nSy
1144 dimList(2,2) = 1
1145 dimList(3,2) = nPy*nSy
1146 dimList(1,3) = 1
1147 dimList(2,3) = 1
1148 dimList(3,3) = 1
1149 ndims=1
1150 call MDSWRITEMETA( metaFName, dataFName,
1151 & filePrec, ndims, dimList, irecord, myIter )
1152 endif
1153
1154 _END_MASTER( myThid )
1155 C ------------------------------------------------------------------
1156 return
1157 end
1158 C=======================================================================
1159
1160 C=======================================================================
1161 subroutine MDS_WRITE_RS_VEC( dUnit, irec, narr, arr )
1162 C IN:
1163 C dunit integer - 'Opened' I/O channel
1164 C irec integer - record number to write
1165 C narr integer - dimension off array "arr"
1166 C arr _RS - model tiled vector
1167 C
1168 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1169
1170 implicit none
1171 C Arguments
1172 integer dUnit
1173 integer irec
1174 integer narr
1175 _RS arr(narr)
1176 C Local
1177 C ------------------------------------------------------------------
1178 write(0,*) 'MDS_WRITE_RS_VEC: irec=',irec,narr
1179 write(dUnit,rec=irec) arr
1180 C ------------------------------------------------------------------
1181 return
1182 end
1183 C=======================================================================
1184
1185 C=======================================================================
1186 subroutine MDS_WRITE_RL_VEC( dUnit, irec, narr, arr )
1187 C IN:
1188 C dunit integer - 'Opened' I/O channel
1189 C irec integer - record number to write
1190 C narr integer - dimension off array "arr"
1191 C arr _RL - model tiled vector
1192 C
1193 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1194
1195 implicit none
1196 C Arguments
1197 integer dUnit
1198 integer irec
1199 integer narr
1200 _RL arr(narr)
1201 C Local
1202 C ------------------------------------------------------------------
1203 write(0,*) 'MDS_WRITE_RL_VEC: irec=',irec,narr
1204 write(dUnit,rec=irec) arr
1205 C ------------------------------------------------------------------
1206 return
1207 end
1208 C=======================================================================
1209
1210 C=======================================================================
1211 subroutine MDS_READ_RS_VEC( dUnit, irec, narr, arr )
1212 C IN:
1213 C dunit integer - 'Opened' I/O channel
1214 C irec integer - record number to write
1215 C narr integer - dimension off array "arr"
1216 C OUT:
1217 C arr _RS - model tiled vector
1218 C
1219 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1220
1221 implicit none
1222 C Arguments
1223 integer dUnit
1224 integer irec
1225 integer narr
1226 _RS arr(narr)
1227 C Local
1228 C ------------------------------------------------------------------
1229 read(dUnit,rec=irec) arr
1230 C ------------------------------------------------------------------
1231 return
1232 end
1233 C=======================================================================
1234
1235 C=======================================================================
1236 subroutine MDS_READ_RL_VEC( dUnit, irec, narr, arr )
1237 C IN:
1238 C dunit integer - 'Opened' I/O channel
1239 C irec integer - record number to write
1240 C narr integer - dimension off array "arr"
1241 C OUT:
1242 C arr _RL - model tiled vector
1243 C
1244 C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1245
1246 implicit none
1247 C Arguments
1248 integer dUnit
1249 integer irec
1250 integer narr
1251 _RL arr(narr)
1252 C Local
1253 C ------------------------------------------------------------------
1254 read(dUnit,rec=irec) arr
1255 C ------------------------------------------------------------------
1256 return
1257 end
1258 C=======================================================================
1259
1260 #ifdef _BYTESWAPIO
1261 C=======================================================================
1262 subroutine MDS_BYTESWAPR4( n, arr )
1263 C IN:
1264 C n integer - Number of 4-byte words in arr
1265 C IN/OUT:
1266 C arr real*4 - Array declared as real*4(n)
1267 C
1268 C Created: 05/05/99 adcroft@mit.edu (This is an unfortunate hack!!)
1269
1270 implicit none
1271 C Arguments
1272 integer n
1273 character*(*) arr
1274 C Local
1275 integer i
1276 character*(1) cc
1277 C ------------------------------------------------------------------
1278 do i=1,4*n,4
1279 cc=arr(i:i)
1280 arr(i:i)=arr(i+3:i+3)
1281 arr(i+3:i+3)=cc
1282 cc=arr(i+1:i+1)
1283 arr(i+1:i+1)=arr(i+2:i+2)
1284 arr(i+2:i+2)=cc
1285 enddo
1286 C ------------------------------------------------------------------
1287 return
1288 end
1289 C=======================================================================
1290
1291 C=======================================================================
1292 subroutine MDS_BYTESWAPR8( n, arr )
1293 C IN:
1294 C n integer - Number of 8-byte words in arr
1295 C IN/OUT:
1296 C arr real*8 - Array declared as real*4(n)
1297 C
1298 C Created: 05/05/99 adcroft@mit.edu (This is an unfortunate hack!!)
1299
1300 implicit none
1301 C Arguments
1302 integer n
1303 character*(*) arr
1304 C Local
1305 integer i
1306 character*(1) cc
1307 C ------------------------------------------------------------------
1308 do i=1,8*n,8
1309 cc=arr(i:i)
1310 arr(i:i)=arr(i+7:i+7)
1311 arr(i+7:i+7)=cc
1312 cc=arr(i+1:i+1)
1313 arr(i+1:i+1)=arr(i+6:i+6)
1314 arr(i+6:i+6)=cc
1315 cc=arr(i+2:i+2)
1316 arr(i+2:i+2)=arr(i+5:i+5)
1317 arr(i+5:i+5)=cc
1318 cc=arr(i+3:i+3)
1319 arr(i+3:i+3)=arr(i+4:i+4)
1320 arr(i+4:i+4)=cc
1321 enddo
1322 C ------------------------------------------------------------------
1323 return
1324 end
1325 C=======================================================================
1326 #endif

  ViewVC Help
Powered by ViewVC 1.1.22