/[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.3 - (hide annotations) (download)
Sun Feb 4 14:38:44 2001 UTC (23 years, 4 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint36, checkpoint35, pre38tag1, pre38-close, checkpoint37
Branch point for: pre38
Changes since 1.2: +2 -1 lines
Made sure each .F and .h file had
the CVS keywords Header and Name at its start.
Most had header but very few currently have Name, so
lots of changes!

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

  ViewVC Help
Powered by ViewVC 1.1.22