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

Diff of /MITgcm/pkg/mdsio/mdsio_readfield_loc.F

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

revision 1.1 by heimbach, Wed Jul 16 16:36:28 2003 UTC revision 1.2 by heimbach, Fri Jul 18 21:10:50 2003 UTC
# Line 0  Line 1 
1    C $Header$
2    C $Name$
3    
4    #include "MDSIO_OPTIONS.h"
5    
6          SUBROUTINE MDSREADFIELD_LOC(
7         I   fName,
8         I   filePrec,
9         I   arrType,
10         I   nNz,
11         O   arr,
12         I   irecord,
13         I   myThid )
14    C
15    C Arguments:
16    C
17    C fName         string  base name for file to read
18    C filePrec      integer number of bits per word in file (32 or 64)
19    C arrType       char(2) declaration of "arr": either "RS" or "RL"
20    C nNz           integer size of third dimension: normally either 1 or Nr
21    C arr           RS/RL   array to read into, arr(:,:,nNz,:,:)
22    C irecord       integer record number to read
23    C myThid        integer thread identifier
24    C
25    C MDSREADFIELD first checks to see if the file "fName" exists, then
26    C if the file "fName.data" exists and finally the tiled files of the
27    C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
28    C read because it is difficult to parse files in fortran.
29    C The precision of the file is decsribed by filePrec, set either
30    C to floatPrec32 or floatPrec64. The precision or declaration of
31    C the array argument must be consistently described by the char*(2)
32    C string arrType, either "RS" or "RL". nNz allows for both 2-D and
33    C 3-D arrays to be handled. nNz=1 implies a 2-D model field and
34    C nNz=Nr implies a 3-D model field. irecord is the record number
35    C to be read and must be >= 1. The file data is stored in
36    C arr *but* the overlaps are *not* updated. ie. An exchange must
37    C be called. This is because the routine is sometimes called from
38    C within a MASTER_THID region.
39    C
40    C Created: 03/16/99 adcroft@mit.edu
41    
42          implicit none
43    C Global variables / common blocks
44    #include "SIZE.h"
45    #include "EEPARAMS.h"
46    #include "PARAMS.h"
47    
48    C Routine arguments
49          character*(*) fName
50          integer filePrec
51          character*(2) arrType
52          integer nNz
53          Real arr(*)
54          integer irecord
55          integer myThid
56    C Functions
57          integer ILNBLNK
58          integer MDS_RECLEN
59    C Local variables
60          character*(80) dataFName
61          integer iG,jG,irec,bi,bj,j,k,dUnit,IL
62          logical exst
63          Real*4 r4seg(sNx)
64          Real*8 r8seg(sNx)
65          logical globalFile,fileIsOpen
66          integer length_of_rec
67          character*(max_len_mbuf) msgbuf
68    C     ------------------------------------------------------------------
69    
70    C Only do I/O if I am the master thread
71          _BEGIN_MASTER( myThid )
72    
73    C Record number must be >= 1
74          if (irecord .LT. 1) then
75           write(msgbuf,'(a,i9.8)')
76         &   ' MDSREADFIELD: argument irecord = ',irecord
77           call print_message( msgbuf, standardmessageunit,
78         &                     SQUEEZE_RIGHT , mythid)
79           write(msgbuf,'(a)')
80         &   ' MDSREADFIELD: Invalid value for irecord'
81           call print_error( msgbuf, mythid )
82           stop 'ABNORMAL END: S/R MDSREADFIELD'
83          endif
84    
85    C Assume nothing
86          globalFile = .FALSE.
87          fileIsOpen = .FALSE.
88          IL=ILNBLNK( fName )
89    
90    C Assign a free unit number as the I/O channel for this routine
91          call MDSFINDUNIT( dUnit, mythid )
92    
93    C Check first for global file with simple name (ie. fName)
94          dataFName = fName
95          inquire( file=dataFname, exist=exst )
96          if (exst) then
97           if ( debugLevel .GE. debLevA ) then
98            write(msgbuf,'(a,a)')
99         &   ' MDSREADFIELD: opening global file: ',dataFName
100            call print_message( msgbuf, standardmessageunit,
101         &                     SQUEEZE_RIGHT , mythid)
102           endif
103           globalFile = .TRUE.
104          endif
105    
106    C If negative check for global file with MDS name (ie. fName.data)
107          if (.NOT. globalFile) then
108           write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
109           inquire( file=dataFname, exist=exst )
110           if (exst) then
111            if ( debugLevel .GE. debLevA ) then
112             write(msgbuf,'(a,a)')
113         &    ' MDSREADFIELD: opening global file: ',dataFName
114             call print_message( msgbuf, standardmessageunit,
115         &                      SQUEEZE_RIGHT , mythid)
116            endif
117            globalFile = .TRUE.
118           endif
119          endif
120    
121    C If we are reading from a global file then we open it here
122          if (globalFile) then
123           length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
124           open( dUnit, file=dataFName, status='old',
125         &      access='direct', recl=length_of_rec )
126           fileIsOpen=.TRUE.
127          endif
128    
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+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
135             jG=bj+(myYGlobalLo-1)/sNy ! 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              if ( debugLevel .GE. debLevA ) then
143               write(msgbuf,'(a,a)')
144         &      ' MDSREADFIELD: opening file: ',dataFName
145               call print_message( msgbuf, standardmessageunit,
146         &                        SQUEEZE_RIGHT , mythid)
147              endif
148              length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
149              open( dUnit, file=dataFName, status='old',
150         &        access='direct', recl=length_of_rec )
151              fileIsOpen=.TRUE.
152             else
153              fileIsOpen=.FALSE.
154              write(msgbuf,'(a,a)')
155         &      ' MDSREADFIELD: filename: ',dataFName
156              call print_message( msgbuf, standardmessageunit,
157         &                        SQUEEZE_RIGHT , mythid)
158              write(msgbuf,'(a)')
159         &      ' MDSREADFIELD: File does not exist'
160              call print_error( msgbuf, mythid )
161              stop 'ABNORMAL END: S/R MDSREADFIELD'
162             endif
163            endif
164    
165            if (fileIsOpen) then
166             do k=1,nNz
167              do j=1,sNy
168               if (globalFile) then
169                iG = myXGlobalLo-1 + (bi-1)*sNx
170                jG = myYGlobalLo-1 + (bj-1)*sNy
171                irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
172         &             + nSx*nPx*Ny*nNz*(irecord-1)
173               else
174                iG = 0
175                jG = 0
176                irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
177               endif
178               if (filePrec .eq. precFloat32) then
179                read(dUnit,rec=irec) r4seg
180    #ifdef _BYTESWAPIO
181                call MDS_BYTESWAPR4( sNx, r4seg )
182    #endif
183                if (arrType .eq. 'RS') then
184                 call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
185                elseif (arrType .eq. 'RL') then
186                 call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
187                else
188                 write(msgbuf,'(a)')
189         &         ' MDSREADFIELD: illegal value for arrType'
190                 call print_error( msgbuf, mythid )
191                 stop 'ABNORMAL END: S/R MDSREADFIELD'
192                endif
193               elseif (filePrec .eq. precFloat64) then
194                read(dUnit,rec=irec) r8seg
195    #ifdef _BYTESWAPIO
196                call MDS_BYTESWAPR8( sNx, r8seg )
197    #endif
198                if (arrType .eq. 'RS') then
199                 call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
200                elseif (arrType .eq. 'RL') then
201                 call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
202                else
203                 write(msgbuf,'(a)')
204         &         ' MDSREADFIELD: illegal value for arrType'
205                 call print_error( msgbuf, mythid )
206                 stop 'ABNORMAL END: S/R MDSREADFIELD'
207                endif
208               else
209                write(msgbuf,'(a)')
210         &        ' MDSREADFIELD: illegal value for filePrec'
211                call print_error( msgbuf, mythid )
212                stop 'ABNORMAL END: S/R MDSREADFIELD'
213               endif
214    C End of j loop
215              enddo
216    C End of k loop
217             enddo
218             if (.NOT. globalFile) then
219              close( dUnit )
220              fileIsOpen = .FALSE.
221             endif
222            endif
223    C End of bi,bj loops
224           enddo
225          enddo
226    
227    C If global file was opened then close it
228          if (fileIsOpen .AND. globalFile) then
229           close( dUnit )
230           fileIsOpen = .FALSE.
231          endif
232    
233          _END_MASTER( myThid )
234    
235    C     ------------------------------------------------------------------
236          return
237          end

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22