/[MITgcm]/MITgcm_contrib/high_res_cube/code-mods/mdsio_readfield.F
ViewVC logotype

Annotation of /MITgcm_contrib/high_res_cube/code-mods/mdsio_readfield.F

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


Revision 1.1 - (hide annotations) (download)
Mon Nov 17 23:44:15 2003 UTC (21 years, 7 months ago) by cnh
Branch: MAIN
CVS Tags: checkpoint52d_pre, hrcube_1, checkpoint52a_post
Code to allow reading in pickup with standard cube layout (2*nr+2*nb+2*ng,max(nr,ng,nb))
instead of nsx*snx, nsy*sny

1 cnh 1.1 C $Header: /u/u0/gcmpack/MITgcm/pkg/mdsio/mdsio_readfield.F,v 1.1 2001/03/06 15:28:54 adcroft Exp $
2     C $Name: checkpoint51 $
3    
4     #include "MDSIO_OPTIONS.h"
5    
6     SUBROUTINE MDSREADFIELD(
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     C modified: 11/07/03 afe@ocean.mit.edu
42    
43     implicit none
44     C Global variables / common blocks
45     #include "SIZE.h"
46     #include "EEPARAMS.h"
47     #include "PARAMS.h"
48     #define USE_W2
49     #ifdef USE_W2
50     #include "W2_EXCH2_TOPOLOGY.h"
51     #include "W2_EXCH2_PARAMS.h"
52     #endif
53    
54    
55     C Routine arguments
56     character*(*) fName
57     integer filePrec
58     character*(2) arrType
59     integer nNz
60     Real arr(*)
61     integer irecord
62     integer myThid
63     C Functions
64     integer ILNBLNK
65     integer MDS_RECLEN
66     C Local variables
67     character*(80) dataFName
68     integer iG,jG,irec,bi,bj,j,k,dUnit,IL
69     logical exst
70     Real*4 r4seg(sNx)
71     Real*8 r8seg(sNx)
72     logical globalFile,fileIsOpen
73     integer length_of_rec
74     character*(max_len_mbuf) msgbuf
75     integer domainHeight,domainLength,tby,tgx,tny,tnx,tn
76     C ------------------------------------------------------------------
77    
78     C Only do I/O if I am the master thread
79     _BEGIN_MASTER( myThid )
80    
81     C Record number must be >= 1
82     if (irecord .LT. 1) then
83     write(msgbuf,'(a,i9.8)')
84     & ' MDSREADFIELD: argument irecord = ',irecord
85     call print_message( msgbuf, standardmessageunit,
86     & SQUEEZE_RIGHT , mythid)
87     write(msgbuf,'(a)')
88     & ' MDSREADFIELD: Invalid value for irecord'
89     call print_error( msgbuf, mythid )
90     stop 'ABNORMAL END: S/R MDSREADFIELD'
91     endif
92    
93     C Assume nothing
94     globalFile = .FALSE.
95     fileIsOpen = .FALSE.
96     IL=ILNBLNK( fName )
97    
98     C Assign a free unit number as the I/O channel for this routine
99     call MDSFINDUNIT( dUnit, mythid )
100    
101     C Check first for global file with simple name (ie. fName)
102     dataFName = fName
103     inquire( file=dataFname, exist=exst )
104     if (exst) then
105     write(msgbuf,'(a,a)')
106     & ' MDSREADFIELD: opening global file: ',dataFName
107     call print_message( msgbuf, standardmessageunit,
108     & SQUEEZE_RIGHT , mythid)
109     globalFile = .TRUE.
110     endif
111    
112     C If negative check for global file with MDS name (ie. fName.data)
113     if (.NOT. globalFile) then
114     write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
115     inquire( file=dataFname, exist=exst )
116     if (exst) then
117     write(msgbuf,'(a,a)')
118     & ' MDSREADFIELD: opening global file: ',dataFName
119     call print_message( msgbuf, standardmessageunit,
120     & SQUEEZE_RIGHT , mythid)
121     globalFile = .TRUE.
122     endif
123     endif
124    
125     C If we are reading from a global file then we open it here
126     if (globalFile) then
127     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
128     open( dUnit, file=dataFName, status='old',
129     & access='direct', recl=length_of_rec )
130     fileIsOpen=.TRUE.
131     endif
132    
133     #ifdef USE_W2
134    
135     c domainLength = 2*ng+2*nb+2*nr
136     c domainLength = 2*1+2*1+2*1
137     c domainLength =nsx
138     c domainLength = nsx / int(sqrt( nsx/6.0 ))
139     c domainHeight= int(sqrt( nsx/6.0 ))
140     domainLength = exch2_domain_nxt
141     domainHeight = exch2_domain_nyt
142    
143     write(*,fmt='(1X,A,I3,A,I3)') 'L=', domainlength,
144     & 'H=', domainheight
145     C Loop over all tiles
146     do bj=1,nSy
147     do bi=1,nSx
148     C If we are reading from a tiled MDS file then we open each one here
149     if (.NOT. globalFile) then
150     write(msgbuf,'(a)')
151     & ' MDSREADFIELD: non-global input files not
152     & implemented with exch2'
153     call print_error( msgbuf, mythid )
154     stop 'ABNORMAL END: S/R MDSREADFIELD'
155     endif
156     tn = W2_myTileList(bi)
157     tby = exch2_tbasey(tn)
158     tgx = exch2_txglobalo(tn)
159     tny = exch2_tny(tn)
160     tnx = exch2_tnx(tn)
161     if (fileIsOpen) then
162     do k=1,nNz
163     do j=1,tNy
164     write(*,fmt='(1X,A,I3,A,I3,A,I3,A,I3,A,I3,A,I3)') 'tby=', tby,
165     & ', tgx=', tgx,
166     & ', tnx=',tnx, ', tny=', tny, ', j=',j,', tn=',tn
167    
168     irec = domainLength*tby + (tgx-1)/tnx + 1 +
169     & domainLength*(j-1) +
170     & domainLength*domainHeight*tny*(k-1) +
171     & domainLength*domainHeight*tny*nNz*(irecord-1)
172     c write(*,fmt='(1X,A,I6,A,I3)') 'record = ',irec,',thingy=',
173     c & (tgx-1)/tnx
174     write(*,fmt='(1X,A,I6)') 'record = ',irec
175    
176     if (filePrec .eq. precFloat32) then
177     read(dUnit,rec=irec) r4seg
178     #ifdef _BYTESWAPIO
179     call MDS_BYTESWAPR4( sNx, r4seg )
180     #endif
181     if (arrType .eq. 'RS') then
182     call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
183     elseif (arrType .eq. 'RL') then
184     call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
185     else
186     write(msgbuf,'(a)')
187     & ' MDSREADFIELD: illegal value for arrType'
188     call print_error( msgbuf, mythid )
189     stop 'ABNORMAL END: S/R MDSREADFIELD'
190     endif
191     elseif (filePrec .eq. precFloat64) then
192     read(dUnit,rec=irec) r8seg
193     #ifdef _BYTESWAPIO
194     call MDS_BYTESWAPR8( sNx, r8seg )
195     #endif
196     if (arrType .eq. 'RS') then
197     call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
198     elseif (arrType .eq. 'RL') then
199     call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
200     else
201     write(msgbuf,'(a)')
202     & ' MDSREADFIELD: illegal value for arrType'
203     call print_error( msgbuf, mythid )
204     stop 'ABNORMAL END: S/R MDSREADFIELD'
205     endif
206     else
207     write(msgbuf,'(a)')
208     & ' MDSREADFIELD: illegal value for filePrec'
209     call print_error( msgbuf, mythid )
210     stop 'ABNORMAL END: S/R MDSREADFIELD'
211     endif
212     C End of j loop
213     enddo
214     C End of k loop
215     enddo
216     if (.NOT. globalFile) then
217     close( dUnit )
218     fileIsOpen = .FALSE.
219     endif
220     endif
221     C End of bi,bj loops
222     enddo
223     enddo
224    
225    
226    
227    
228     #else
229     C don't use W2_exch2
230    
231     C Loop over all tiles
232     do bj=1,nSy
233     do bi=1,nSx
234     C If we are reading from a tiled MDS file then we open each one here
235     if (.NOT. globalFile) then
236     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
237     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
238     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
239     & fName(1:IL),'.',iG,'.',jG,'.data'
240     inquire( file=dataFname, exist=exst )
241     C Of course, we only open the file if the tile is "active"
242     C (This is a place-holder for the active/passive mechanism
243     if (exst) then
244     write(msgbuf,'(a,a)')
245     & ' MDSREADFIELD: opening file: ',dataFName
246     call print_message( msgbuf, standardmessageunit,
247     & SQUEEZE_RIGHT , mythid)
248     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
249     open( dUnit, file=dataFName, status='old',
250     & access='direct', recl=length_of_rec )
251     fileIsOpen=.TRUE.
252     else
253     fileIsOpen=.FALSE.
254     write(msgbuf,'(a,a)')
255     & ' MDSREADFIELD: filename: ',dataFName
256     call print_message( msgbuf, standardmessageunit,
257     & SQUEEZE_RIGHT , mythid)
258     write(msgbuf,'(a)')
259     & ' MDSREADFIELD: File does not exist'
260     call print_error( msgbuf, mythid )
261     stop 'ABNORMAL END: S/R MDSREADFIELD'
262     endif
263     endif
264    
265     if (fileIsOpen) then
266     do k=1,nNz
267     do j=1,sNy
268     if (globalFile) then
269     iG = myXGlobalLo-1 + (bi-1)*sNx
270     jG = myYGlobalLo-1 + (bj-1)*sNy
271     irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
272     & + nSx*nPx*Ny*nNz*(irecord-1)
273     else
274     iG = 0
275     jG = 0
276     irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
277     endif
278     if (filePrec .eq. precFloat32) then
279     read(dUnit,rec=irec) r4seg
280     #ifdef _BYTESWAPIO
281     call MDS_BYTESWAPR4( sNx, r4seg )
282     #endif
283     if (arrType .eq. 'RS') then
284     call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
285     elseif (arrType .eq. 'RL') then
286     call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
287     else
288     write(msgbuf,'(a)')
289     & ' MDSREADFIELD: illegal value for arrType'
290     call print_error( msgbuf, mythid )
291     stop 'ABNORMAL END: S/R MDSREADFIELD'
292     endif
293     elseif (filePrec .eq. precFloat64) then
294     read(dUnit,rec=irec) r8seg
295     #ifdef _BYTESWAPIO
296     call MDS_BYTESWAPR8( sNx, r8seg )
297     #endif
298     if (arrType .eq. 'RS') then
299     call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
300     elseif (arrType .eq. 'RL') then
301     call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
302     else
303     write(msgbuf,'(a)')
304     & ' MDSREADFIELD: illegal value for arrType'
305     call print_error( msgbuf, mythid )
306     stop 'ABNORMAL END: S/R MDSREADFIELD'
307     endif
308     else
309     write(msgbuf,'(a)')
310     & ' MDSREADFIELD: illegal value for filePrec'
311     call print_error( msgbuf, mythid )
312     stop 'ABNORMAL END: S/R MDSREADFIELD'
313     endif
314     C End of j loop
315     enddo
316     C End of k loop
317     enddo
318     if (.NOT. globalFile) then
319     close( dUnit )
320     fileIsOpen = .FALSE.
321     endif
322     endif
323     C End of bi,bj loops
324     enddo
325     enddo
326    
327     #endif
328    
329     C If global file was opened then close it
330     if (fileIsOpen .AND. globalFile) then
331     close( dUnit )
332     fileIsOpen = .FALSE.
333     endif
334    
335    
336    
337     _END_MASTER( myThid )
338    
339     C ------------------------------------------------------------------
340     return
341     end

  ViewVC Help
Powered by ViewVC 1.1.22