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

Annotation of /MITgcm/pkg/mdsio/mdsio_gl.F

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


Revision 1.1 - (hide annotations) (download)
Tue Mar 6 15:28:54 2001 UTC (23 years, 3 months ago) by adcroft
Branch: MAIN
CVS Tags: pre38tag1, pre38-close, checkpoint37
Branch point for: pre38
Packaged mdsio.

Note: using a "feature" of genmake to keep original mdsio.F and mdsio_gl.F
in place during testing of mdsio package. To use original code simply
use genmake -disable=mdsio.
                                             Enjoy.

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

  ViewVC Help
Powered by ViewVC 1.1.22