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

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

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


Revision 1.2 - (hide annotations) (download)
Fri Feb 2 21:04:47 2001 UTC (23 years, 4 months ago) by adcroft
Branch: MAIN
Changes since 1.1: +3 -3 lines
Merged changes from branch "branch-atmos-merge" into MAIN (checkpoint34)
 - substantial modifications to algorithm sequence (dynamics.F)
 - packaged OBCS, Shapiro filter, Zonal filter, Atmospheric Physics

1 adcroft 1.2 C $Header: /u/gcmpack/models/MITgcmUV/eesupp/src/mdsio_gl.F,v 1.1 2001/01/29 20:00:15 heimbach Exp $
2 heimbach 1.1
3     #include "CPP_OPTIONS.h"
4    
5     C The five "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 Modified: 07/27/99 eckert@mit.edu
22     C Customized for state estimation (--> active_file_control.F)
23     C this relates only to *mdsreadvector* and *mdswritevector*
24     C Modified: 07/28/99 eckert@mit.edu
25     C inserted calls to *print_message* and *print_error*
26     C
27     C To be modified to work with MITgcmuv message routines.
28    
29     #undef SAFE_IO
30    
31     #ifdef SAFE_IO
32     #define _NEW_STATUS 'new'
33     #else
34     #define _NEW_STATUS 'unknown'
35     #endif
36    
37     #ifdef ALLOW_AUTODIFF_TAMC
38     #define _OLD_STATUS 'unknown'
39     #else
40     #define _OLD_STATUS 'old'
41     #endif
42    
43     C=======================================================================
44     SUBROUTINE MDSREADFIELD_GL(
45     I fName,
46     I filePrec,
47     I arrType,
48     I nNz,
49     O arr_gl,
50     I irecord,
51     I myThid )
52     C
53     C Arguments:
54     C
55     C fName string base name for file to read
56     C filePrec integer number of bits per word in file (32 or 64)
57     C arrType char(2) declaration of "arr": either "RS" or "RL"
58     C nNz integer size of third dimension: normally either 1 or Nr
59     C arr RS/RL array to read into, arr(:,:,nNz,:,:)
60     C irecord integer record number to read
61     C myThid integer thread identifier
62     C
63     C MDSREADFIELD first checks to see if the file "fName" exists, then
64     C if the file "fName.data" exists and finally the tiled files of the
65     C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
66     C read because it is difficult to parse files in fortran.
67     C The precision of the file is decsribed by filePrec, set either
68     C to floatPrec32 or floatPrec64. The precision or declaration of
69     C the array argument must be consistently described by the char*(2)
70     C string arrType, either "RS" or "RL". nNz allows for both 2-D and
71     C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
72     C nNz=Nr implies a 3-D model field. irecord is the record number
73     C to be read and must be >= 1. The file data is stored in
74     C arr *but* the overlaps are *not* updated. ie. An exchange must
75     C be called. This is because the routine is sometimes called from
76     C within a MASTER_THID region.
77     C
78     C Created: 03/16/99 adcroft@mit.edu
79    
80     implicit none
81     C Global variables / common blocks
82     #include "SIZE.h"
83     #include "EEPARAMS.h"
84     #include "PARAMS.h"
85    
86     C Routine arguments
87     character*(*) fName
88     integer filePrec
89     character*(2) arrType
90     integer nNz
91     _RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,nNz)
92     integer irecord
93     integer myThid
94     C Functions
95     integer ILNBLNK
96     integer MDS_RECLEN
97     C Local variables
98     character*(80) dataFName
99     integer ip,jp,iG,jG,irec,bi,bj,ii,j,k,dUnit,IL
100     logical exst
101 adcroft 1.2 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy)
102 heimbach 1.1 Real*4 r4seg(sNx)
103     Real*8 r8seg(sNx)
104     logical globalFile,fileIsOpen
105     integer length_of_rec
106     character*(max_len_mbuf) msgbuf
107     C ------------------------------------------------------------------
108    
109     C Only do I/O if I am the master thread
110     _BEGIN_MASTER( myThid )
111    
112     C Record number must be >= 1
113     if (irecord .LT. 1) then
114     write(msgbuf,'(a,i9.8)')
115     & ' MDSREADFIELD_GL: argument irecord = ',irecord
116     call print_message( msgbuf, standardmessageunit,
117     & SQUEEZE_RIGHT , mythid)
118     write(msgbuf,'(a)')
119     & ' MDSREADFIELD_GL: Invalid value for irecord'
120     call print_error( msgbuf, mythid )
121     stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
122     endif
123    
124     C Assume nothing
125     globalFile = .FALSE.
126     fileIsOpen = .FALSE.
127     IL=ILNBLNK( fName )
128    
129     C Assign a free unit number as the I/O channel for this routine
130     call MDSFINDUNIT( dUnit, mythid )
131    
132     C Check first for global file with simple name (ie. fName)
133     dataFName = fName
134     inquire( file=dataFname, exist=exst )
135     if (exst) then
136     write(msgbuf,'(a,a)')
137     & ' MDSREADFIELD: opening global file: ',dataFName
138     call print_message( msgbuf, standardmessageunit,
139     & SQUEEZE_RIGHT , mythid)
140     stop " xx, adxx, weights and masks are not supposed to be global"
141     endif
142    
143     C If negative check for global file with MDS name (ie. fName.data)
144     if (.NOT. globalFile) then
145     write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
146     inquire( file=dataFname, exist=exst )
147     if (exst) then
148     write(msgbuf,'(a,a)')
149     & ' MDSREADFIELD_GL: opening global file: ',dataFName
150     call print_message( msgbuf, standardmessageunit,
151     & SQUEEZE_RIGHT , mythid)
152     globalFile = .TRUE.
153     stop " xx, adxx, weights and masks are not supposed to be global"
154     endif
155     endif
156     C Loop over all processors
157     do jp=1,nPy
158     do ip=1,nPx
159     C Loop over all tiles
160     do bj=1,nSy
161     do bi=1,nSx
162     C If we are reading from a tiled MDS file then we open each one here
163     if (.NOT. globalFile) then
164     iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
165     jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
166     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
167     & fName(1:IL),'.',iG,'.',jG,'.data'
168     inquire( file=dataFname, exist=exst )
169     C Of course, we only open the file if the tile is "active"
170     C (This is a place-holder for the active/passive mechanism
171     if (exst) then
172     write(msgbuf,'(a,a)')
173     & ' MDSREADFIELD_GL: opening file: ',dataFName
174     call print_message( msgbuf, standardmessageunit,
175     & SQUEEZE_RIGHT , mythid)
176     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
177     open( dUnit, file=dataFName, status='old',
178     & access='direct', recl=length_of_rec )
179     fileIsOpen=.TRUE.
180     else
181     fileIsOpen=.FALSE.
182     write(msgbuf,'(a,a)')
183     & ' MDSREADFIELD_GL: filename: ',dataFName
184     call print_message( msgbuf, standardmessageunit,
185     & SQUEEZE_RIGHT , mythid)
186     write(msgbuf,'(a)')
187     & ' MDSREADFIELD_GL: File does not exist'
188     call print_error( msgbuf, mythid )
189     stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
190     endif
191     endif
192    
193     if (fileIsOpen) then
194     do k=1,nNz
195     do j=1,sNy
196     iG = 0
197     jG = 0
198     irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
199     if (filePrec .eq. precFloat32) then
200     read(dUnit,rec=irec) r4seg
201     #ifdef _BYTESWAPIO
202     call MDS_BYTESWAPR4( sNx, r4seg )
203     #endif
204     if (arrType .eq. 'RS') then
205     call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
206     elseif (arrType .eq. 'RL') then
207     call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
208     else
209     write(msgbuf,'(a)')
210     & ' MDSREADFIELD_GL: illegal value for arrType'
211     call print_error( msgbuf, mythid )
212     stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
213     endif
214     elseif (filePrec .eq. precFloat64) then
215     read(dUnit,rec=irec) r8seg
216     #ifdef _BYTESWAPIO
217     call MDS_BYTESWAPR8( sNx, r8seg )
218     #endif
219     if (arrType .eq. 'RS') then
220     call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
221     elseif (arrType .eq. 'RL') then
222     call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
223     else
224     write(msgbuf,'(a)')
225     & ' MDSREADFIELD_GL: illegal value for arrType'
226     call print_error( msgbuf, mythid )
227     stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
228     endif
229     else
230     write(msgbuf,'(a)')
231     & ' MDSREADFIELD_GL: illegal value for filePrec'
232     call print_error( msgbuf, mythid )
233     stop 'ABNORMAL END: S/R MDSREADFIELD_GL'
234     endif
235     do ii=1,sNx
236     arr_gl(ii,bi,ip,j,bj,jp,k)=arr(ii,j,k,bi,bj)
237     enddo
238    
239     C End of j loop
240     enddo
241     C End of k loop
242     enddo
243     if (.NOT. globalFile) then
244     close( dUnit )
245     fileIsOpen = .FALSE.
246     endif
247     endif
248     C End of bi,bj loops
249     enddo
250     enddo
251     C End of ip,jp loops
252     enddo
253     enddo
254    
255     C If global file was opened then close it
256     if (fileIsOpen .AND. globalFile) then
257     close( dUnit )
258     fileIsOpen = .FALSE.
259     endif
260    
261     _END_MASTER( myThid )
262    
263     C ------------------------------------------------------------------
264     return
265     end
266     C=======================================================================
267    
268     C=======================================================================
269     SUBROUTINE MDSWRITEFIELD_GL(
270     I fName,
271     I filePrec,
272     I arrType,
273     I nNz,
274     I arr_gl,
275     I irecord,
276     I myIter,
277     I myThid )
278     C
279     C Arguments:
280     C
281     C fName string base name for file to written
282     C filePrec integer number of bits per word in file (32 or 64)
283     C arrType char(2) declaration of "arr": either "RS" or "RL"
284     C nNz integer size of third dimension: normally either 1 or Nr
285     C arr RS/RL array to write, arr(:,:,nNz,:,:)
286     C irecord integer record number to read
287     C myIter integer time step number
288     C myThid integer thread identifier
289     C
290     C MDSWRITEFIELD creates either a file of the form "fName.data" and
291     C "fName.meta" if the logical flag "globalFile" is set true. Otherwise
292     C it creates MDS tiled files of the form "fName.xxx.yyy.data" and
293     C "fName.xxx.yyy.meta". A meta-file is always created.
294     C Currently, the meta-files are not read because it is difficult
295     C to parse files in fortran. We should read meta information before
296     C adding records to an existing multi-record file.
297     C The precision of the file is decsribed by filePrec, set either
298     C to floatPrec32 or floatPrec64. The precision or declaration of
299     C the array argument must be consistently described by the char*(2)
300     C string arrType, either "RS" or "RL". nNz allows for both 2-D and
301     C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
302     C nNz=Nr implies a 3-D model field. irecord is the record number
303     C to be read and must be >= 1. NOTE: It is currently assumed that
304     C the highest record number in the file was the last record written.
305     C Nor is there a consistency check between the routine arguments and file.
306     C ie. if your write record 2 after record 4 the meta information
307     C will record the number of records to be 2. This, again, is because
308     C we have read the meta information. To be fixed.
309     C
310     C Created: 03/16/99 adcroft@mit.edu
311     C
312     C Changed: 05/31/00 heimbach@mit.edu
313     C open(dUnit, ..., status='old', ... -> status='unknown'
314    
315     implicit none
316     C Global variables / common blocks
317     #include "SIZE.h"
318     #include "EEPARAMS.h"
319     #include "PARAMS.h"
320    
321     C Routine arguments
322     character*(*) fName
323     integer filePrec
324     character*(2) arrType
325     integer nNz
326     cph(
327     cph Real arr(*)
328     _RL arr_gl(sNx,nSx,nPx,sNy,nSy,nPy,nNz)
329     cph)
330     integer irecord
331     integer myIter
332     integer myThid
333     C Functions
334     integer ILNBLNK
335     integer MDS_RECLEN
336     C Local variables
337     character*(80) dataFName,metaFName
338     integer ip,jp,iG,jG,irec,bi,bj,ii,j,k,dUnit,IL
339     Real*4 r4seg(sNx)
340     Real*8 r8seg(sNx)
341 adcroft 1.2 _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,Nr,nSx,nSy)
342 heimbach 1.1 integer dimList(3,3),ndims
343     integer length_of_rec
344     logical fileIsOpen
345     character*(max_len_mbuf) msgbuf
346     C ------------------------------------------------------------------
347    
348     C Only do I/O if I am the master thread
349     _BEGIN_MASTER( myThid )
350    
351     C Record number must be >= 1
352     if (irecord .LT. 1) then
353     write(msgbuf,'(a,i9.8)')
354     & ' MDSWRITEFIELD_GL: argument irecord = ',irecord
355     call print_message( msgbuf, standardmessageunit,
356     & SQUEEZE_RIGHT , mythid)
357     write(msgbuf,'(a)')
358     & ' MDSWRITEFIELD_GL: invalid value for irecord'
359     call print_error( msgbuf, mythid )
360     stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
361     endif
362    
363     C Assume nothing
364     fileIsOpen=.FALSE.
365     IL=ILNBLNK( fName )
366    
367     C Assign a free unit number as the I/O channel for this routine
368     call MDSFINDUNIT( dUnit, mythid )
369    
370    
371     C Loop over all processors
372     do jp=1,nPy
373     do ip=1,nPx
374     C Loop over all tiles
375     do bj=1,nSy
376     do bi=1,nSx
377     C If we are writing to a tiled MDS file then we open each one here
378     iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
379     jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
380     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
381     & fName(1:IL),'.',iG,'.',jG,'.data'
382     if (irecord .EQ. 1) then
383     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
384     open( dUnit, file=dataFName, status=_NEW_STATUS,
385     & access='direct', recl=length_of_rec )
386     fileIsOpen=.TRUE.
387     else
388     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
389     open( dUnit, file=dataFName, status=_OLD_STATUS,
390     & access='direct', recl=length_of_rec )
391     fileIsOpen=.TRUE.
392     endif
393     if (fileIsOpen) then
394     do k=1,nNz
395     do j=1,sNy
396     do ii=1,sNx
397     arr(ii,j,k,bi,bj)=arr_gl(ii,bi,ip,j,bj,jp,k)
398     enddo
399     iG = 0
400     jG = 0
401     irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
402     if (filePrec .eq. precFloat32) then
403     if (arrType .eq. 'RS') then
404     call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
405     elseif (arrType .eq. 'RL') then
406     call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .FALSE., arr )
407     else
408     write(msgbuf,'(a)')
409     & ' MDSWRITEFIELD_GL: illegal value for arrType'
410     call print_error( msgbuf, mythid )
411     stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
412     endif
413     #ifdef _BYTESWAPIO
414     call MDS_BYTESWAPR4( sNx, r4seg )
415     #endif
416     write(dUnit,rec=irec) r4seg
417     elseif (filePrec .eq. precFloat64) then
418     if (arrType .eq. 'RS') then
419     call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
420     elseif (arrType .eq. 'RL') then
421     call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .FALSE., arr )
422     else
423     write(msgbuf,'(a)')
424     & ' MDSWRITEFIELD_GL: illegal value for arrType'
425     call print_error( msgbuf, mythid )
426     stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
427     endif
428     #ifdef _BYTESWAPIO
429     call MDS_BYTESWAPR8( sNx, r8seg )
430     #endif
431     write(dUnit,rec=irec) r8seg
432     else
433     write(msgbuf,'(a)')
434     & ' MDSWRITEFIELD_GL: illegal value for filePrec'
435     call print_error( msgbuf, mythid )
436     stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
437     endif
438     C End of j loop
439     enddo
440     C End of k loop
441     enddo
442     else
443     write(msgbuf,'(a)')
444     & ' MDSWRITEFIELD_GL: I should never get to this point'
445     call print_error( msgbuf, mythid )
446     stop 'ABNORMAL END: S/R MDSWRITEFIELD_GL'
447     endif
448     C If we were writing to a tiled MDS file then we close it here
449     if (fileIsOpen) then
450     close( dUnit )
451     fileIsOpen = .FALSE.
452     endif
453     C Create meta-file for each tile if we are tiling
454     iG=bi+(ip-1)*nsx ! Kludge until unstructered tiles
455     jG=bj+(jp-1)*nsy ! Kludge until unstructered tiles
456     write(metaFname(1:80),'(2a,i3.3,a,i3.3,a)')
457     & fName(1:IL),'.',iG,'.',jG,'.meta'
458     dimList(1,1)=Nx
459     dimList(2,1)=((ip-1)*nSx+(bi-1))*sNx+1
460     dimList(3,1)=((ip-1)*nSx+bi)*sNx
461     dimList(1,2)=Ny
462     dimList(2,2)=((jp-1)*nSy+(bj-1))*sNy+1
463     dimList(3,2)=((jp-1)*nSy+bj)*sNy
464     dimList(1,3)=Nr
465     dimList(2,3)=1
466     dimList(3,3)=Nr
467     ndims=3
468     if (nNz .EQ. 1) ndims=2
469     call MDSWRITEMETA( metaFName, dataFName,
470     & filePrec, ndims, dimList, irecord, myIter, mythid )
471     C End of bi,bj loops
472     enddo
473     enddo
474     C End of ip,jp loops
475     enddo
476     enddo
477    
478    
479     _END_MASTER( myThid )
480    
481     C ------------------------------------------------------------------
482     return
483     end
484     C=======================================================================

  ViewVC Help
Powered by ViewVC 1.1.22