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

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

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


Revision 1.2 - (hide annotations) (download)
Fri May 7 18:14:16 1999 UTC (25 years ago) by adcroft
Branch: MAIN
Changes since 1.1: +81 -1 lines
Added a byte swapping routine for the Linux platform so that
g77 compiled code can read/write big-endian data. This ought not
be a permanent feature of mdsio.F but it's not clear how to
better deal with this other than use little endian data.

1 adcroft 1.2 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/mdsio.F,v 1.1 1999/05/05 18:32:34 adcroft Exp $
2 adcroft 1.1
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 adcroft 1.2 #ifdef _BYTESWAPIO
180     call MDS_BYTESWAPR4( sNx, r4seg )
181     #endif
182 adcroft 1.1 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 adcroft 1.2 #ifdef _BYTESWAPIO
192     call MDS_BYTESWAPR8( sNx, r8seg )
193     #endif
194 adcroft 1.1 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 adcroft 1.2 #ifdef _BYTESWAPIO
380     call MDS_BYTESWAPR4( sNx, r4seg )
381     #endif
382 adcroft 1.1 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 adcroft 1.2 #ifdef _BYTESWAPIO
392     call MDS_BYTESWAPR8( sNx, r8seg )
393     #endif
394 adcroft 1.1 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     write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
413     & fName(1:IL),'.',bi,'.',bj,'.meta'
414     dimList(1,1)=Nx
415     dimList(2,1)=myXGlobalLo+(bi-1)*sNx
416     dimList(3,1)=myXGlobalLo+bi*sNx-1
417     dimList(1,2)=Ny
418     dimList(2,2)=myYGlobalLo+(bj-1)*sNy
419     dimList(3,2)=myYGlobalLo+bj*sNy-1
420     dimList(1,3)=Nr
421     dimList(2,3)=1
422     dimList(3,3)=Nr
423     ndims=3
424     if (nNz .EQ. 1) ndims=2
425     call MDSWRITEMETA( metaFName, dataFName,
426     & filePrec, ndims, dimList, irecord, myIter )
427     endif
428     C End of bi,bj loops
429     enddo
430     enddo
431    
432     C If global file was opened then close it
433     if (fileIsOpen .AND. globalFile) then
434     close( dUnit )
435     fileIsOpen = .FALSE.
436     endif
437    
438     C Create meta-file for the global-file
439     if (globalFile) then
440     C We can't do this operation using threads (yet) because of the
441     C "barrier" at the next step. The barrier could be removed but
442     C at the cost of "safe" distributed I/O.
443     if (nThreads.NE.1) then
444     write(0,*)
445     & 'MDSWRITEFIELD: A threads version of this routine does not exist'
446     write(0,*) 'MDSWRITEFIELD: This needs to be fixed...'
447     write(0,*) 'MDSWRITEFIELD: nThreads = ',nThreads
448     stop 'MDSWRITEFIELD: Stopping because you are using threads'
449     endif
450     C We put a barrier here to ensure that all processes have finished
451     C writing their data before we update the meta-file
452     _BARRIER
453     write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
454     dimList(1,1)=Nx
455     dimList(2,1)=1
456     dimList(3,1)=Nx
457     dimList(1,2)=Ny
458     dimList(2,2)=1
459     dimList(3,2)=Ny
460     dimList(1,3)=Nr
461     dimList(2,3)=1
462     dimList(3,3)=Nr
463     ndims=3
464     if (nNz .EQ. 1) ndims=2
465     call MDSWRITEMETA( metaFName, dataFName,
466     & filePrec, ndims, dimList, irecord, myIter )
467     fileIsOpen=.TRUE.
468     endif
469    
470     _END_MASTER( myThid )
471    
472     C ------------------------------------------------------------------
473     return
474     end
475     C=======================================================================
476    
477     C=======================================================================
478     subroutine MDS_SEG4toRS( j,bi,bj,k,nNz, seg, copyTo, arr )
479     C IN:
480     C j,bi,bj,k integer - indices to array "arr"
481     C nNz integer - K dimension of array "arr"
482     C seg Real*4 - 1-D vector of length sNx
483     C OUT:
484     C arr _RS - model tiled array
485     C
486     C Created: 03/20/99 adcroft@mit.edu
487    
488     implicit none
489     C Global variables / common blocks
490     #include "SIZE.h"
491    
492     C Arguments
493     integer j,bi,bj,k,nNz
494     _RS arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
495     logical copyTo
496     Real*4 seg(sNx)
497     C Local
498     integer ii
499    
500     C ------------------------------------------------------------------
501    
502     if (copyTo) then
503     do ii=1,sNx
504     arr(ii,j,k,bi,bj)=seg(ii)
505     enddo
506     else
507     do ii=1,sNx
508     seg(ii)=arr(ii,j,k,bi,bj)
509     enddo
510     endif
511    
512     C ------------------------------------------------------------------
513     return
514     end
515     C=======================================================================
516    
517     C=======================================================================
518     subroutine MDS_SEG4toRL( j,bi,bj,k,nNz, seg, copyTo, arr )
519     C IN:
520     C j,bi,bj,k integer - indices to array "arr"
521     C nNz integer - K dimension of array "arr"
522     C seg Real*4 - 1-D vector of length sNx
523     C OUT:
524     C arr _RL - model tiled array
525     C
526     C Created: 03/20/99 adcroft@mit.edu
527    
528     implicit none
529     C Global variables / common blocks
530     #include "SIZE.h"
531    
532     C Arguments
533     integer j,bi,bj,k,nNz
534     _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
535     logical copyTo
536     Real*4 seg(sNx)
537     C Local
538     integer ii
539     C ------------------------------------------------------------------
540     if (copyTo) then
541     do ii=1,sNx
542     arr(ii,j,k,bi,bj)=seg(ii)
543     enddo
544     else
545     do ii=1,sNx
546     seg(ii)=arr(ii,j,k,bi,bj)
547     enddo
548     endif
549     C ------------------------------------------------------------------
550     return
551     end
552     C=======================================================================
553    
554     C=======================================================================
555     subroutine MDS_SEG8toRS( j,bi,bj,k,nNz, seg, copyTo, arr )
556     C IN:
557     C j,bi,bj,k integer - indices to array "arr"
558     C nNz integer - K dimension of array "arr"
559     C seg Real*8 - 1-D vector of length sNx
560     C OUT:
561     C arr _RS - model tiled array
562     C
563     C Created: 03/20/99 adcroft@mit.edu
564    
565     implicit none
566     C Global variables / common blocks
567     #include "SIZE.h"
568    
569     C Arguments
570     integer j,bi,bj,k,nNz
571     _RS arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
572     logical copyTo
573     Real*8 seg(sNx)
574     C Local
575     integer ii
576     C ------------------------------------------------------------------
577     if (copyTo) then
578     do ii=1,sNx
579     arr(ii,j,k,bi,bj)=seg(ii)
580     enddo
581     else
582     do ii=1,sNx
583     seg(ii)=arr(ii,j,k,bi,bj)
584     enddo
585     endif
586     C ------------------------------------------------------------------
587     return
588     end
589     C=======================================================================
590    
591     C=======================================================================
592     subroutine MDS_SEG8toRL( j,bi,bj,k,nNz, seg, copyTo, arr )
593     C IN:
594     C j,bi,bj,k integer - indices to array "arr"
595     C nNz integer - K dimension of array "arr"
596     C seg Real*8 - 1-D vector of length sNx
597     C OUT:
598     C arr _RL - model tiled array
599     C
600     C Created: 03/20/99 adcroft@mit.edu
601    
602     implicit none
603     C Global variables / common blocks
604     #include "SIZE.h"
605    
606     C Arguments
607     integer j,bi,bj,k,nNz
608     _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
609     logical copyTo
610     Real*8 seg(sNx)
611     C Local
612     integer ii
613     C ------------------------------------------------------------------
614     if (copyTo) then
615     do ii=1,sNx
616     arr(ii,j,k,bi,bj)=seg(ii)
617     enddo
618     else
619     do ii=1,sNx
620     seg(ii)=arr(ii,j,k,bi,bj)
621     enddo
622     endif
623     C ------------------------------------------------------------------
624     return
625     end
626     C=======================================================================
627    
628     C=======================================================================
629     subroutine MDSWRITEMETA(
630     I mFileName,
631     I dFileName,
632     I filePrec,
633     I ndims,
634     I dimList,
635     I nrecords,
636     I myIter )
637    
638     C IN:
639     C mFileName string - complete name of meta-file
640     C ndims integer - number of dimensions
641     C dimList integer - array of dimensions, etc.
642     C nrecords integer - record number
643     C myIter integer - time-step number
644     C OUT:
645     C
646     C Created: 03/20/99 adcroft@mit.edu
647    
648     implicit none
649     C Arguments
650     character*(*) mFileName
651     character*(*) dFileName
652     integer filePrec
653     integer ndims
654     integer dimList(3,ndims)
655     integer nrecords
656     integer myIter
657    
658     C Global variables / common blocks
659     #include "SIZE.h"
660     #include "EEPARAMS.h"
661     #include "PARAMS.h"
662    
663     C Functions
664     integer ILNBLNK
665     C Local
666     integer i,ii,mUnit
667     logical ex
668     C ------------------------------------------------------------------
669    
670     C We should *read* the met-file if it exists to check
671     C that the information we are writing is consistent
672     C with the current contents
673     inquire( file=mFileName, exist=ex )
674     C However, it is bloody difficult to parse files
675     C in fortran so someone else can do this.
676     C For now, we will assume everything is ok
677     C and that the last record is written to the
678     C last consecutive record in the file.
679    
680     C Assign a free unit number as the I/O channel for this subroutine
681     call MDSFINDUNIT( mUnit )
682    
683     C Open meta-file
684     open( mUnit, file=mFileName, status='unknown',
685     & form='formatted' )
686    
687     C Write the number of dimensions
688     write(mUnit,'(x,a,i3,a)') 'nDims = [ ',ndims,' ];'
689    
690     C For each dimension, write the following:
691     C 1 global size (ie. the size of the global dimension of all files)
692     C 2 global start (ie. the global position of the start of this file)
693     C 3 global end (ie. the global position of the end of this file)
694    
695     write(mUnit,'(x,a)') 'dimList = ['
696     do ii=1,ndims
697     if (ii.lt.ndims) then
698     write(mUnit,'(10x,3(i5,","))') (dimList(i,ii),i=1,3)
699     else
700     write(mUnit,'(10x,i5,",",i5,",",i5)') (dimList(i,ii),i=1,3)
701     endif
702     enddo
703     write(mUnit,'(10x,a)') '];'
704    
705     C Record the precision of the file
706     if (filePrec .EQ. precFloat32) then
707     write(mUnit,'(x,a)') "format = [ 'float32' ];"
708     elseif (filePrec .EQ. precFloat64) then
709     write(mUnit,'(x,a)') "format = [ 'float64' ];"
710     else
711     stop 'MDSWRITEMETA: invalid filePrec'
712     endif
713    
714     C Record the current record number
715     C This is a proxy for the actual number of records in the file.
716     C If we could read the file then we could do this properly.
717     write(mUnit,'(x,a,i5,a)') 'nrecords = [ ',nrecords,' ];'
718    
719     C Record the file-name for the binary data
720     Cveto ii=ILNBLNK( dFileName )
721     Cveto write(mUnit,'(x,3a)') 'binarydatafile = [ ',dFileName(1:ii),' ];'
722    
723     C Write the integer time (integer iteration number) for later record
724     C keeping. If the timestep number is less than 0 then we assume
725     C that the information is superfluous and do not write it.
726     if (myIter .ge. 0)
727     & write(mUnit,'(x,a,i8,a)') 'timeStepNumber = [ ',myIter,' ];'
728    
729     C Close meta-file
730     close(mUnit)
731    
732     C ------------------------------------------------------------------
733     return
734     end
735     C=======================================================================
736    
737     C=======================================================================
738     subroutine MDSFINDUNIT( iounit )
739     C OUT:
740     C iounit integer - unit number
741     C
742     C MDSFINDUNIT returns a valid, unused unit number for f77 I/O
743     C The routine stops the program is an error occurs in the process
744     C of searching the I/O channels.
745     C
746     C Created: 03/20/99 adcroft@mit.edu
747    
748     implicit none
749     C Arguments
750     integer iounit
751     C Local
752     integer ii
753     logical op
754     integer ios
755     C ------------------------------------------------------------------
756    
757     C Sweep through a valid range of unit numbers
758     iounit=-1
759     do ii=9,99
760     if (iounit.eq.-1) then
761     inquire(unit=ii,iostat=ios,opened=op)
762     if (ios.ne.0) then
763     write(0,*) 'MDSFINDUNIT: inquiring unit number =',ii
764     stop 'MDSFINDUNIT: inquire statement failed!'
765     endif
766     if (.NOT. op) then
767     iounit=ii
768     endif
769     endif
770     enddo
771    
772     C Was there an available unit number
773     if (iounit.eq.-1) then
774     stop 'MDSFINDUNIT: could not find an available unit number!'
775     endif
776    
777     C ------------------------------------------------------------------
778     return
779     end
780     C=======================================================================
781    
782     C=======================================================================
783     integer function MDS_RECLEN( filePrec, nnn )
784     C IN:
785     C filePrec integer - precision of file in bits
786     C nnn integer - number of elements in record
787     C OUT:
788     C MDS_RECLEN integer - appropriate length of record in bytes or words
789     C
790     C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
791    
792     implicit none
793     C Arguments
794     integer filePrec
795     integer nnn
796     C Global variables
797     #include "SIZE.h"
798     #include "EEPARAMS.h"
799     #include "PARAMS.h"
800     C Local
801     C ------------------------------------------------------------------
802    
803     if (filePrec .EQ. precFloat32) then
804     MDS_RECLEN=nnn*WORDLENGTH
805     elseif (filePrec .EQ. precFloat64) then
806     MDS_RECLEN=nnn*WORDLENGTH*2
807     else
808     write(0,*) 'MDS_RECLEN: filePrec = ',filePrec
809     stop 'MDS_RECLEN: Illegal value for filePrec'
810     endif
811    
812     C ------------------------------------------------------------------
813     return
814     end
815     C=======================================================================
816    
817     C=======================================================================
818     SUBROUTINE MDSREADVECTOR(
819     I fName,
820     I filePrec,
821     I arrType,
822     I narr,
823     O arr,
824     I irecord,
825     I myThid )
826     C
827     C Arguments:
828     C
829     C fName string base name for file to read
830     C filePrec integer number of bits per word in file (32 or 64)
831     C arrType char(2) declaration of "arr": either "RS" or "RL"
832     C narr integer size of third dimension: normally either 1 or Nr
833     C arr RS/RL array to read into, arr(narr)
834     C irecord integer record number to read
835     C myThid integer thread identifier
836     C
837     C Created: 03/26/99 eckert@mit.edu
838     C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
839     C Fixed to work work with _RS and _RL declarations
840    
841     implicit none
842     C Global variables / common blocks
843     #include "SIZE.h"
844     #include "EEPARAMS.h"
845     #include "PARAMS.h"
846    
847     C Routine arguments
848     character*(*) fName
849     integer filePrec
850     character*(2) arrType
851     integer narr
852     Real arr(narr)
853     integer irecord
854     integer myThid
855     C Functions
856     integer ILNBLNK
857     integer MDS_RECLEN
858     C Local variables
859     character*(80) dataFName
860     integer iG,jG,irec,bi,bj,dUnit,IL
861     logical exst
862     logical globalFile,fileIsOpen
863     integer length_of_rec
864     C ------------------------------------------------------------------
865    
866     C Only do I/O if I am the master thread
867     _BEGIN_MASTER( myThid )
868    
869     C Record number must be >= 1
870     if (irecord .LT. 1) then
871     write(0,'(a,i)') 'MDSREADVECTOR: argument irecord = ',irecord
872     stop 'MDSREADVECTOR: *ERROR* Invalid value for irecord'
873     endif
874    
875     C Assume nothing
876     globalFile = .FALSE.
877     fileIsOpen = .FALSE.
878     IL=ILNBLNK( fName )
879    
880     C Assign a free unit number as the I/O channel for this routine
881     call MDSFINDUNIT( dUnit )
882    
883     C Check first for global file with simple name (ie. fName)
884     dataFName = fName
885     inquire( file=dataFname, exist=exst )
886     if (exst) then
887     write(0,'(2a)') 'MDSREADVECTOR: opening global file: ',dataFName
888     globalFile = .TRUE.
889     endif
890    
891     C If negative check for global file with MDS name (ie. fName.data)
892     if (.NOT. globalFile) then
893     write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
894     inquire( file=dataFname, exist=exst )
895     if (exst) then
896     write(0,'(2a)') 'MDSREADVECTOR: opening global file: ',dataFName
897     globalFile = .TRUE.
898     endif
899     endif
900    
901     C If we are reading from a global file then we open it here
902     if (globalFile) then
903     length_of_rec=MDS_RECLEN( filePrec, narr )
904     open( dUnit, file=dataFName, status='old',
905     & access='direct', recl=length_of_rec )
906     fileIsOpen=.TRUE.
907     endif
908    
909     C Loop over all tiles
910     do bj=1,nSy
911     do bi=1,nSx
912     C If we are reading from a tiled MDS file then we open each one here
913     if (.NOT. globalFile) then
914     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
915     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
916     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
917     & fName(1:IL),'.',iG,'.',jG,'.data'
918     inquire( file=dataFname, exist=exst )
919     C Of course, we only open the file if the tile is "active"
920     C (This is a place-holder for the active/passive mechanism)
921     if (exst) then
922     write(0,'(2a)') 'MDSREADVECTOR: opening file: ',dataFName
923     length_of_rec=MDS_RECLEN( filePrec, narr )
924     open( dUnit, file=dataFName, status='old',
925     & access='direct', recl=length_of_rec )
926     fileIsOpen=.TRUE.
927     else
928     fileIsOpen=.FALSE.
929     stop 'MDSREADVECTOR: un-active tiles not implemented yet'
930     endif
931     endif
932     if (fileIsOpen) then
933     if (globalFile) then
934     iG = myXGlobalLo-1+(bi-1)*sNx
935     jG = myYGlobalLo-1+(bj-1)*sNy
936     irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
937     & (irecord-1)*nSx*nPx*nSy*nPy
938     else
939     iG = 0
940     jG = 0
941     irec = irecord
942     endif
943     if (filePrec .eq. precFloat32) then
944     call MDS_READ_RS_VEC( dUnit, irec, narr, arr )
945     elseif (filePrec .eq. precFloat64) then
946     call MDS_READ_RL_VEC( dUnit, irec, narr, arr )
947     else
948     stop 'MDSREADVECTOR: illegal value for filePrec'
949     endif
950     if (.NOT. globalFile) then
951     close( dUnit )
952     fileIsOpen = .FALSE.
953     endif
954     endif
955     C End of bi,bj loops
956     enddo
957     enddo
958    
959     C If global file was opened then close it
960     if (fileIsOpen .AND. globalFile) then
961     close( dUnit )
962     fileIsOpen = .FALSE.
963     endif
964    
965     _END_MASTER( myThid )
966    
967     C ------------------------------------------------------------------
968     return
969     end
970     C=======================================================================
971    
972     C=======================================================================
973     SUBROUTINE MDSWRITEVECTOR(
974     I fName,
975     I filePrec,
976     I globalfile,
977     I arrType,
978     I narr,
979     I arr,
980     I irecord,
981     I myIter,
982     I myThid )
983     C Arguments:
984     C
985     C fName string base name for file to written
986     C filePrec integer number of bits per word in file (32 or 64)
987     C globalFile logical selects between writing a global or tiled file
988     C arrType char(2) declaration of "arr": either "RS" or "RL"
989     C narr integer size of third dimension: normally either 1 or Nr
990     C arr RS/RL array to write, arr(narr)
991     C irecord integer record number to read
992     C myIter integer time step number
993     C myThid integer thread identifier
994     C
995     C Created: 03/26/99 eckert@mit.edu
996     C Modified: 03/29/99 adcroft@mit.edu + eckert@mit.edu
997     C Fixed to work work with _RS and _RL declarations
998    
999     implicit none
1000     C Global variables / common blocks
1001     #include "SIZE.h"
1002     #include "EEPARAMS.h"
1003     #include "PARAMS.h"
1004    
1005     C Routine arguments
1006     character*(*) fName
1007     integer filePrec
1008     logical globalfile
1009     character*(2) arrType
1010     integer narr
1011     Real arr(narr)
1012     integer irecord
1013     integer myIter
1014     integer myThid
1015     C Functions
1016     integer ILNBLNK
1017     integer MDS_RECLEN
1018     C Local variables
1019     character*(80) dataFName,metaFName
1020     integer iG,jG,irec,bi,bj,dUnit,IL
1021     logical fileIsOpen
1022     integer dimList(3,3),ndims
1023     integer length_of_rec
1024     C ------------------------------------------------------------------
1025    
1026     C Only do I/O if I am the master thread
1027     _BEGIN_MASTER( myThid )
1028    
1029     C Record number must be >= 1
1030     if (irecord .LT. 1) then
1031     write(0,'(a,i)') 'MDSWRITEVECTOR: argument irecord = ',irecord
1032     stop 'MDSWRITEVECTOR: *ERROR* Invalid value for irecord'
1033     endif
1034    
1035     C Assume nothing
1036     fileIsOpen = .FALSE.
1037     IL=ILNBLNK( fName )
1038    
1039     C Assign a free unit number as the I/O channel for this routine
1040     call MDSFINDUNIT( dUnit )
1041    
1042     C If we are writing to a global file then we open it here
1043     if (globalFile) then
1044     write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
1045     if (irecord .EQ. 1) then
1046     length_of_rec = MDS_RECLEN( filePrec, narr )
1047     open( dUnit, file=dataFName, status=_NEW_STATUS,
1048     & access='direct', recl=length_of_rec )
1049     fileIsOpen=.TRUE.
1050     else
1051     length_of_rec = MDS_RECLEN( filePrec, narr )
1052     open( dUnit, file=dataFName, status='old',
1053     & access='direct', recl=length_of_rec )
1054     fileIsOpen=.TRUE.
1055     endif
1056     endif
1057    
1058     C Loop over all tiles
1059     do bj=1,nSy
1060     do bi=1,nSx
1061     C If we are writing to a tiled MDS file then we open each one here
1062     if (.NOT. globalFile) then
1063     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
1064     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
1065     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
1066     & fName(1:IL),'.',iG,'.',jG,'.data'
1067     if (irecord .EQ. 1) then
1068     length_of_rec = MDS_RECLEN( filePrec, narr )
1069     open( dUnit, file=dataFName, status=_NEW_STATUS,
1070     & access='direct', recl=length_of_rec )
1071     fileIsOpen=.TRUE.
1072     else
1073     length_of_rec = MDS_RECLEN( filePrec, narr )
1074     open( dUnit, file=dataFName, status='old',
1075     & access='direct', recl=length_of_rec )
1076     fileIsOpen=.TRUE.
1077     endif
1078     endif
1079     if (fileIsOpen) then
1080     if (globalFile) then
1081     iG = myXGlobalLo-1+(bi-1)*sNx
1082     jG = myYGlobalLo-1+(bj-1)*sNy
1083     irec = 1 + int(iG/sNx) + (jG/sNy)*nSx*nPx +
1084     & (irecord-1)*nSx*nPx*nSy*nPy
1085     else
1086     iG = 0
1087     jG = 0
1088     irec = irecord
1089     endif
1090     if (filePrec .eq. precFloat32) then
1091     call MDS_WRITE_RS_VEC( dUnit, irec, narr, arr )
1092     elseif (filePrec .eq. precFloat64) then
1093     call MDS_WRITE_RL_VEC( dUnit, irec, narr, arr )
1094     else
1095     stop 'MDSWRITEVECTOR: illegal value for filePrec'
1096     endif
1097     else
1098     stop 'MDSWRITEVECTOR: I should not ever get to this point'
1099     endif
1100     C If we were writing to a tiled MDS file then we close it here
1101     if (fileIsOpen .AND. (.NOT. globalFile)) then
1102     close( dUnit )
1103     fileIsOpen = .FALSE.
1104     endif
1105     C Create meta-file for each tile file
1106     if (.NOT. globalFile) then
1107     write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
1108     & fName(1:IL),'.',bi,'.',bj,'.meta'
1109     dimList(1,1) = nPx*nSx*narr
1110     dimList(2,1) = (int(myXGlobalLo/sNx)+(bi-1))*narr
1111     dimList(3,1) = (int(myXGlobalLo/sNx)+ bi )*narr - 1
1112     dimList(1,2) = nPy*nSy
1113     dimList(2,2) = int(myYGlobalLo/sNy) + bj - 1
1114     dimList(3,2) = int(myYGlobalLo/sNy) + bj - 1
1115     dimList(1,3) = 1
1116     dimList(2,3) = 1
1117     dimList(3,3) = 1
1118     ndims=1
1119     call MDSWRITEMETA( metaFName, dataFName,
1120     & filePrec, ndims, dimList, irecord, myIter )
1121     endif
1122     C End of bi,bj loops
1123     enddo
1124     enddo
1125    
1126     C If global file was opened then close it
1127     if (fileIsOpen .AND. globalFile) then
1128     close( dUnit )
1129     fileIsOpen = .FALSE.
1130     endif
1131    
1132     C Create meta-file for global file
1133     if (globalFile) then
1134     write(metaFName(1:80),'(2a)') fName(1:IL),'.meta'
1135     dimList(1,1) = nPx*nSx*narr
1136     dimList(2,1) = 1
1137     dimList(3,1) = nPx*nSx*narr
1138     dimList(1,2) = nPy*nSy
1139     dimList(2,2) = 1
1140     dimList(3,2) = nPy*nSy
1141     dimList(1,3) = 1
1142     dimList(2,3) = 1
1143     dimList(3,3) = 1
1144     ndims=1
1145     call MDSWRITEMETA( metaFName, dataFName,
1146     & filePrec, ndims, dimList, irecord, myIter )
1147     endif
1148    
1149     _END_MASTER( myThid )
1150     C ------------------------------------------------------------------
1151     return
1152     end
1153     C=======================================================================
1154    
1155     C=======================================================================
1156     subroutine MDS_WRITE_RS_VEC( dUnit, irec, narr, arr )
1157     C IN:
1158     C dunit integer - 'Opened' I/O channel
1159     C irec integer - record number to write
1160     C narr integer - dimension off array "arr"
1161     C arr _RS - model tiled vector
1162     C
1163     C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1164    
1165     implicit none
1166     C Arguments
1167     integer dUnit
1168     integer irec
1169     integer narr
1170     _RS arr(narr)
1171     C Local
1172     C ------------------------------------------------------------------
1173     write(0,*) 'MDS_WRITE_RS_VEC: irec=',irec,narr
1174     write(dUnit,rec=irec) arr
1175     C ------------------------------------------------------------------
1176     return
1177     end
1178     C=======================================================================
1179    
1180     C=======================================================================
1181     subroutine MDS_WRITE_RL_VEC( dUnit, irec, narr, arr )
1182     C IN:
1183     C dunit integer - 'Opened' I/O channel
1184     C irec integer - record number to write
1185     C narr integer - dimension off array "arr"
1186     C arr _RL - model tiled vector
1187     C
1188     C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1189    
1190     implicit none
1191     C Arguments
1192     integer dUnit
1193     integer irec
1194     integer narr
1195     _RL arr(narr)
1196     C Local
1197     C ------------------------------------------------------------------
1198     write(0,*) 'MDS_WRITE_RL_VEC: irec=',irec,narr
1199     write(dUnit,rec=irec) arr
1200     C ------------------------------------------------------------------
1201     return
1202     end
1203     C=======================================================================
1204    
1205     C=======================================================================
1206     subroutine MDS_READ_RS_VEC( dUnit, irec, narr, arr )
1207     C IN:
1208     C dunit integer - 'Opened' I/O channel
1209     C irec integer - record number to write
1210     C narr integer - dimension off array "arr"
1211     C OUT:
1212     C arr _RS - model tiled vector
1213     C
1214     C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1215    
1216     implicit none
1217     C Arguments
1218     integer dUnit
1219     integer irec
1220     integer narr
1221     _RS arr(narr)
1222     C Local
1223     C ------------------------------------------------------------------
1224     read(dUnit,rec=irec) arr
1225     C ------------------------------------------------------------------
1226     return
1227     end
1228     C=======================================================================
1229    
1230     C=======================================================================
1231     subroutine MDS_READ_RL_VEC( dUnit, irec, narr, arr )
1232     C IN:
1233     C dunit integer - 'Opened' I/O channel
1234     C irec integer - record number to write
1235     C narr integer - dimension off array "arr"
1236     C OUT:
1237     C arr _RL - model tiled vector
1238     C
1239     C Created: 03/29/99 eckert@mit.edu + adcroft@mit.edu
1240    
1241     implicit none
1242     C Arguments
1243     integer dUnit
1244     integer irec
1245     integer narr
1246     _RL arr(narr)
1247     C Local
1248     C ------------------------------------------------------------------
1249     read(dUnit,rec=irec) arr
1250     C ------------------------------------------------------------------
1251     return
1252     end
1253     C=======================================================================
1254 adcroft 1.2
1255     #ifdef _BYTESWAPIO
1256     C=======================================================================
1257     subroutine MDS_BYTESWAPR4( n, arr )
1258     C IN:
1259     C n integer - Number of 4-byte words in arr
1260     C IN/OUT:
1261     C arr real*4 - Array declared as real*4(n)
1262     C
1263     C Created: 05/05/99 adcroft@mit.edu (This is an unfortunate hack!!)
1264    
1265     implicit none
1266     C Arguments
1267     integer n
1268     character*(*) arr
1269     C Local
1270     integer i
1271     character*(1) cc
1272     C ------------------------------------------------------------------
1273     do i=1,4*n,4
1274     cc=arr(i:i)
1275     arr(i:i)=arr(i+3:i+3)
1276     arr(i+3:i+3)=cc
1277     cc=arr(i+1:i+1)
1278     arr(i+1:i+1)=arr(i+2:i+2)
1279     arr(i+2:i+2)=cc
1280     enddo
1281     C ------------------------------------------------------------------
1282     return
1283     end
1284     C=======================================================================
1285    
1286     C=======================================================================
1287     subroutine MDS_BYTESWAPR8( n, arr )
1288     C IN:
1289     C n integer - Number of 8-byte words in arr
1290     C IN/OUT:
1291     C arr real*8 - Array declared as real*4(n)
1292     C
1293     C Created: 05/05/99 adcroft@mit.edu (This is an unfortunate hack!!)
1294    
1295     implicit none
1296     C Arguments
1297     integer n
1298     character*(*) arr
1299     C Local
1300     integer i
1301     character*(1) cc
1302     C ------------------------------------------------------------------
1303     do i=1,8*n,8
1304     cc=arr(i:i)
1305     arr(i:i)=arr(i+7:i+7)
1306     arr(i+7:i+7)=cc
1307     cc=arr(i+1:i+1)
1308     arr(i+1:i+1)=arr(i+6:i+6)
1309     arr(i+6:i+6)=cc
1310     cc=arr(i+2:i+2)
1311     arr(i+2:i+2)=arr(i+5:i+5)
1312     arr(i+5:i+5)=cc
1313     cc=arr(i+3:i+3)
1314     arr(i+3:i+3)=arr(i+4:i+4)
1315     arr(i+4:i+4)=cc
1316     enddo
1317     C ------------------------------------------------------------------
1318     return
1319     end
1320     C=======================================================================
1321     #endif

  ViewVC Help
Powered by ViewVC 1.1.22