/[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.2 - (hide annotations) (download)
Sun Jan 25 01:06:12 2004 UTC (21 years, 5 months ago) by dimitri
Branch: MAIN
CVS Tags: hrcube_2
Changes since 1.1: +151 -123 lines
replaced mdsio_readfield.F with older version from main branch

1 dimitri 1.2 C $Header: /usr/local/gcmpack/MITgcm/pkg/mdsio/mdsio_readfield.F,v 1.6 2003/12/10 00:41:01 dimitri Exp $
2     C $Name: hrcube_1 $
3 cnh 1.1
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    
42     implicit none
43     C Global variables / common blocks
44     #include "SIZE.h"
45     #include "EEPARAMS.h"
46     #include "PARAMS.h"
47 dimitri 1.2 #include "EESUPPORT.h"
48 cnh 1.1
49     C Routine arguments
50     character*(*) fName
51     integer filePrec
52     character*(2) arrType
53     integer nNz
54     Real arr(*)
55     integer irecord
56     integer myThid
57     C Functions
58     integer ILNBLNK
59     integer MDS_RECLEN
60     C Local variables
61 dimitri 1.2 character*(80) dataFName,pfName
62     integer iG,jG,irec,bi,bj,j,k,dUnit,IL,pIL
63 cnh 1.1 logical exst
64     Real*4 r4seg(sNx)
65     Real*8 r8seg(sNx)
66     logical globalFile,fileIsOpen
67     integer length_of_rec
68     character*(max_len_mbuf) msgbuf
69 dimitri 1.2 integer i
70     Real*4 global_r4(Nx,Ny)
71     Real*8 global (Nx,Ny)
72     _RL local(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
73 cnh 1.1 C ------------------------------------------------------------------
74    
75     C Only do I/O if I am the master thread
76     _BEGIN_MASTER( myThid )
77    
78     C Record number must be >= 1
79     if (irecord .LT. 1) then
80     write(msgbuf,'(a,i9.8)')
81     & ' MDSREADFIELD: argument irecord = ',irecord
82     call print_message( msgbuf, standardmessageunit,
83     & SQUEEZE_RIGHT , mythid)
84     write(msgbuf,'(a)')
85     & ' MDSREADFIELD: Invalid value for irecord'
86     call print_error( msgbuf, mythid )
87     stop 'ABNORMAL END: S/R MDSREADFIELD'
88     endif
89    
90     C Assume nothing
91     globalFile = .FALSE.
92     fileIsOpen = .FALSE.
93 dimitri 1.2 IL = ILNBLNK( fName )
94     pIL = ILNBLNK( mdsioLocalDir )
95    
96     C Assign special directory
97     if ( mdsioLocalDir .NE. ' ' ) then
98     write(pFname(1:80),'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
99     else
100     pFname= fName
101     endif
102     pIL=ILNBLNK( pfName )
103 cnh 1.1
104     C Assign a free unit number as the I/O channel for this routine
105     call MDSFINDUNIT( dUnit, mythid )
106    
107     C Check first for global file with simple name (ie. fName)
108     dataFName = fName
109     inquire( file=dataFname, exist=exst )
110     if (exst) then
111 dimitri 1.2 if ( debugLevel .GE. debLevA ) then
112     write(msgbuf,'(a,a)')
113 cnh 1.1 & ' MDSREADFIELD: opening global file: ',dataFName
114 dimitri 1.2 call print_message( msgbuf, standardmessageunit,
115 cnh 1.1 & SQUEEZE_RIGHT , mythid)
116 dimitri 1.2 endif
117 cnh 1.1 globalFile = .TRUE.
118     endif
119    
120     C If negative check for global file with MDS name (ie. fName.data)
121     if (.NOT. globalFile) then
122     write(dataFname(1:80),'(2a)') fName(1:IL),'.data'
123     inquire( file=dataFname, exist=exst )
124     if (exst) then
125 dimitri 1.2 if ( debugLevel .GE. debLevA ) then
126     write(msgbuf,'(a,a)')
127 cnh 1.1 & ' MDSREADFIELD: opening global file: ',dataFName
128 dimitri 1.2 call print_message( msgbuf, standardmessageunit,
129 cnh 1.1 & SQUEEZE_RIGHT , mythid)
130 dimitri 1.2 endif
131 cnh 1.1 globalFile = .TRUE.
132     endif
133     endif
134    
135 dimitri 1.2 if ( .not. ( globalFile .and. useSingleCPUIO ) ) then
136    
137 cnh 1.1 C If we are reading from a global file then we open it here
138     if (globalFile) then
139     length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
140     open( dUnit, file=dataFName, status='old',
141     & access='direct', recl=length_of_rec )
142     fileIsOpen=.TRUE.
143     endif
144    
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     iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
151     jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
152     write(dataFname(1:80),'(2a,i3.3,a,i3.3,a)')
153 dimitri 1.2 & pfName(1:pIL),'.',iG,'.',jG,'.data'
154 cnh 1.1 inquire( file=dataFname, exist=exst )
155     C Of course, we only open the file if the tile is "active"
156     C (This is a place-holder for the active/passive mechanism
157     if (exst) then
158 dimitri 1.2 if ( debugLevel .GE. debLevA ) then
159     write(msgbuf,'(a,a)')
160 cnh 1.1 & ' MDSREADFIELD: opening file: ',dataFName
161 dimitri 1.2 call print_message( msgbuf, standardmessageunit,
162 cnh 1.1 & SQUEEZE_RIGHT , mythid)
163 dimitri 1.2 endif
164 cnh 1.1 length_of_rec=MDS_RECLEN( filePrec, sNx, mythid )
165     open( dUnit, file=dataFName, status='old',
166     & access='direct', recl=length_of_rec )
167     fileIsOpen=.TRUE.
168     else
169     fileIsOpen=.FALSE.
170 dimitri 1.2 write(msgbuf,'(3a)')
171     & ' MDSREADFIELD: filename: ',dataFName, pfName
172 cnh 1.1 call print_message( msgbuf, standardmessageunit,
173     & SQUEEZE_RIGHT , mythid)
174     write(msgbuf,'(a)')
175     & ' MDSREADFIELD: File does not exist'
176     call print_error( msgbuf, mythid )
177     stop 'ABNORMAL END: S/R MDSREADFIELD'
178     endif
179     endif
180    
181     if (fileIsOpen) then
182     do k=1,nNz
183     do j=1,sNy
184     if (globalFile) then
185     iG = myXGlobalLo-1 + (bi-1)*sNx
186     jG = myYGlobalLo-1 + (bj-1)*sNy
187     irec=1 + INT(iG/sNx) + nSx*nPx*(jG+j-1) + nSx*nPx*Ny*(k-1)
188     & + nSx*nPx*Ny*nNz*(irecord-1)
189     else
190     iG = 0
191     jG = 0
192     irec=j + sNy*(k-1) + sNy*nNz*(irecord-1)
193     endif
194     if (filePrec .eq. precFloat32) then
195     read(dUnit,rec=irec) r4seg
196     #ifdef _BYTESWAPIO
197     call MDS_BYTESWAPR4( sNx, r4seg )
198     #endif
199     if (arrType .eq. 'RS') then
200     call MDS_SEG4toRS( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
201     elseif (arrType .eq. 'RL') then
202     call MDS_SEG4toRL( j,bi,bj,k,nNz, r4seg, .TRUE., arr )
203     else
204     write(msgbuf,'(a)')
205     & ' MDSREADFIELD: illegal value for arrType'
206     call print_error( msgbuf, mythid )
207     stop 'ABNORMAL END: S/R MDSREADFIELD'
208     endif
209     elseif (filePrec .eq. precFloat64) then
210     read(dUnit,rec=irec) r8seg
211     #ifdef _BYTESWAPIO
212     call MDS_BYTESWAPR8( sNx, r8seg )
213     #endif
214     if (arrType .eq. 'RS') then
215     call MDS_SEG8toRS( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
216     elseif (arrType .eq. 'RL') then
217     call MDS_SEG8toRL( j,bi,bj,k,nNz, r8seg, .TRUE., arr )
218     else
219     write(msgbuf,'(a)')
220     & ' MDSREADFIELD: illegal value for arrType'
221     call print_error( msgbuf, mythid )
222     stop 'ABNORMAL END: S/R MDSREADFIELD'
223     endif
224     else
225     write(msgbuf,'(a)')
226     & ' MDSREADFIELD: illegal value for filePrec'
227     call print_error( msgbuf, mythid )
228     stop 'ABNORMAL END: S/R MDSREADFIELD'
229     endif
230     C End of j loop
231     enddo
232     C End of k loop
233     enddo
234     if (.NOT. globalFile) then
235     close( dUnit )
236     fileIsOpen = .FALSE.
237     endif
238     endif
239     C End of bi,bj loops
240     enddo
241     enddo
242    
243     C If global file was opened then close it
244     if (fileIsOpen .AND. globalFile) then
245     close( dUnit )
246     fileIsOpen = .FALSE.
247     endif
248    
249 dimitri 1.2 endif
250     c endif ( .not. ( globalFile .and. useSingleCPUIO ) )
251 cnh 1.1
252 dimitri 1.2 _END_MASTER( myThid )
253    
254     if ( globalFile .and. useSingleCPUIO ) then
255    
256     C master thread of process 0, only, opens a global file
257     _BEGIN_MASTER( myThid )
258     #ifdef ALLOW_USE_MPI
259     IF( mpiMyId .EQ. 0 ) THEN
260     #else
261     IF ( .TRUE. ) THEN
262     #endif /* ALLOW_USE_MPI */
263     length_of_rec=MDS_RECLEN( filePrec, Nx*Ny, mythid )
264     open( dUnit, file=dataFName, status='old',
265     & access='direct', recl=length_of_rec )
266     ENDIF
267     _END_MASTER( myThid )
268    
269     DO k=1,nNz
270    
271     _BEGIN_MASTER( myThid )
272     #ifdef ALLOW_USE_MPI
273     IF( mpiMyId .EQ. 0 ) THEN
274     #else
275     IF ( .TRUE. ) THEN
276     #endif /* ALLOW_USE_MPI */
277     irec = k+nNz*(irecord-1)
278     if (filePrec .eq. precFloat32) then
279     read(dUnit,rec=irec) global_r4
280     #ifdef _BYTESWAPIO
281     call MDS_BYTESWAPR4( Nx*Ny, global_r4 )
282     #endif
283     DO J=1,Ny
284     DO I=1,Nx
285     global(I,J) = global_r4(I,J)
286     ENDDO
287     ENDDO
288     elseif (filePrec .eq. precFloat64) then
289     read(dUnit,rec=irec) global
290     #ifdef _BYTESWAPIO
291     call MDS_BYTESWAPR8( Nx*Ny, global )
292     #endif
293     else
294     write(msgbuf,'(a)')
295     & ' MDSREADFIELD: illegal value for filePrec'
296     call print_error( msgbuf, mythid )
297     stop 'ABNORMAL END: S/R MDSREADFIELD'
298     endif
299     ENDIF
300     _END_MASTER( myThid )
301    
302     CALL SCATTER_2D(global,local,mythid)
303     if (arrType .eq. 'RS') then
304     call PASStoRS( local,arr,k,nNz,mythid )
305     elseif (arrType .eq. 'RL') then
306     call PASStoRL( local,arr,k,nNz,mythid )
307     else
308     write(msgbuf,'(a)')
309     & ' MDSREADFIELD: illegal value for arrType'
310     call print_error( msgbuf, mythid )
311     stop 'ABNORMAL END: S/R MDSREADFIELD'
312     endif
313    
314     ENDDO
315     c ENDDO k=1,nNz
316 cnh 1.1
317 dimitri 1.2 _BEGIN_MASTER( myThid )
318     close( dUnit )
319     _END_MASTER( myThid )
320    
321     endif
322     c endif ( globalFile .and. useSingleCPUIO )
323 cnh 1.1
324     C ------------------------------------------------------------------
325 dimitri 1.2 return
326     end
327    
328    
329     C ==================================================================
330    
331     subroutine passToRS(local,arr,k,nNz,mythid)
332     implicit none
333     #include "EEPARAMS.h"
334     #include "SIZE.h"
335     _RL local(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nSx,nSy)
336     integer i,j,k,bi,bj,nNz
337     _RS arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
338     integer mythid
339     DO bj = myByLo(myThid), myByHi(myThid)
340     DO bi = myBxLo(myThid), myBxHi(myThid)
341     DO J=1-Oly,sNy+Oly
342     DO I=1-Olx,sNx+Olx
343     arr(I,J,k,bi,bj) = local(I,J,bi,bj)
344     ENDDO
345     ENDDO
346     ENDDO
347     ENDDO
348     return
349     end
350    
351     subroutine passToRL(local,arr,k,nNz,mythid)
352     implicit none
353     #include "EEPARAMS.h"
354     #include "SIZE.h"
355     _RL local(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nSx,nSy)
356     integer i,j,k,bi,bj,nNz
357     _RL arr(1-oLx:sNx+oLx,1-oLy:sNy+oLy,nNz,nSx,nSy)
358     integer mythid
359     DO bj = myByLo(myThid), myByHi(myThid)
360     DO bi = myBxLo(myThid), myBxHi(myThid)
361     DO J=1-Oly,sNy+Oly
362     DO I=1-Olx,sNx+Olx
363     arr(I,J,k,bi,bj) = local(I,J,bi,bj)
364     ENDDO
365     ENDDO
366     ENDDO
367     ENDDO
368 cnh 1.1 return
369     end

  ViewVC Help
Powered by ViewVC 1.1.22