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

Contents of /MITgcm/pkg/mdsio/mdsio_read_field.F

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


Revision 1.6 - (show annotations) (download)
Mon May 11 02:20:48 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61n
Changes since 1.5: +39 -15 lines
move mapping to global io-buffer inside gather_2d/scater_2d ; save memory
(1 less 2D global RL array) + only send/receive real*4 arr when 32.bit file

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_read_field.F,v 1.5 2009/05/06 02:42:49 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MDS_READ_FIELD
8 C !INTERFACE:
9 SUBROUTINE MDS_READ_FIELD(
10 I fName,
11 I filePrec,
12 I useCurrentDir,
13 I arrType,
14 I kSize,kLo,kHi,
15 O arr,
16 I irecord,
17 I myThid )
18
19 C !DESCRIPTION:
20 C Arguments:
21 C
22 C fName (string) :: base name for file to read
23 C filePrec (integer) :: number of bits per word in file (32 or 64)
24 C useCurrentDir(logic):: always read from the current directory (even if
25 C "mdsioLocalDir" is set)
26 C arrType (char(2)) :: declaration of "arr": either "RS" or "RL"
27 C kSize (integer) :: size of third dimension: normally either 1 or Nr
28 C kLo (integer) :: 1rst vertical level (of array "arr") to read-in
29 C kHi (integer) :: last vertical level (of array "arr") to read-in
30 C arr ( RS/RL ) :: array to read into, arr(:,:,kSize,:,:)
31 C irecord (integer) :: record number to read
32 C myIter (integer) :: time step number
33 C myThid (integer) :: thread identifier
34 C
35 C MDS_READ_FIELD first checks to see IF the file "fName" exists, then
36 C IF the file "fName.data" exists and finally the tiled files of the
37 C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
38 C read because it is difficult to parse files in fortran.
39 C The precision of the file is decsribed by filePrec, set either
40 C to floatPrec32 or floatPrec64. The precision or declaration of
41 C the array argument must be consistently described by the char*(2)
42 C string arrType, either "RS" or "RL".
43 C (kSize,kLo,kHi) allows for both 2-D and 3-D arrays to be handled, with
44 C the option to only read and fill-in a sub-set of consecutive vertical
45 C levels (from kLo to kHi) ; (kSize,kLo,kHi)=(1,1,1) implies a 2-D model
46 C field and (kSize,kLo,kHi)=(Nr,1,Nr) implies a 3-D model field.
47 C irecord is the record number to be read and must be >= 1.
48 C The file data is stored in arr *but* the overlaps are *not* updated,
49 C i.e., an exchange must be called. This is because the routine is
50 C sometimes called from within a MASTER_THID region.
51 C
52 C Created: 03/16/99 adcroft@mit.edu
53 CEOP
54
55 C !USES:
56 IMPLICIT NONE
57 C Global variables / common blocks
58 #include "SIZE.h"
59 #include "EEPARAMS.h"
60 #include "PARAMS.h"
61 #ifdef ALLOW_EXCH2
62 #include "W2_EXCH2_TOPOLOGY.h"
63 #include "W2_EXCH2_PARAMS.h"
64 #endif /* ALLOW_EXCH2 */
65 #include "MDSIO_SCPU.h"
66
67 C !INPUT PARAMETERS:
68 CHARACTER*(*) fName
69 INTEGER filePrec
70 LOGICAL useCurrentDir
71 CHARACTER*(2) arrType
72 INTEGER kSize, kLo, kHi
73 INTEGER irecord
74 INTEGER myThid
75 C !OUTPUT PARAMETERS:
76 Real arr(*)
77
78 C !FUNCTIONS
79 INTEGER ILNBLNK
80 INTEGER MDS_RECLEN
81 LOGICAL MASTER_CPU_IO
82 EXTERNAL ILNBLNK
83 EXTERNAL MDS_RECLEN
84 EXTERNAL MASTER_CPU_IO
85
86 C !LOCAL VARIABLES:
87 CHARACTER*(MAX_LEN_FNAM) dataFName,pfName
88 CHARACTER*(MAX_LEN_MBUF) msgBuf
89 LOGICAL exst
90 LOGICAL globalFile, fileIsOpen
91 LOGICAL iAmDoingIO
92 LOGICAL keepBlankTileIO
93 INTEGER xSize, ySize
94 INTEGER iG,jG,bi,bj,i,j,k,nNz
95 INTEGER irec,dUnit,IL,pIL
96 INTEGER length_of_rec
97 Real*4 r4seg(sNx)
98 Real*8 r8seg(sNx)
99 #ifdef ALLOW_EXCH2
100 INTEGER iGjLoc, jGjLoc
101 c INTEGER tGy,tGx,tNy,tNx,tN
102 INTEGER tGy,tGx, tNx,tN
103 INTEGER global_nTx
104 #endif /* ALLOW_EXCH2 */
105 INTEGER tNy
106
107 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
108 C Set dimensions:
109 xSize = Nx
110 ySize = Ny
111 keepBlankTileIO = .FALSE.
112 #if defined(ALLOW_EXCH2) && !defined(MISSING_TILE_IO)
113 xSize = exch2_global_Nx
114 ySize = exch2_global_Ny
115 keepBlankTileIO = .TRUE.
116 #endif
117
118 C Assume nothing
119 globalFile = .FALSE.
120 fileIsOpen = .FALSE.
121 IL = ILNBLNK( fName )
122 pIL = ILNBLNK( mdsioLocalDir )
123 nNz = 1 + kHi - kLo
124
125 C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO):
126 iAmDoingIO = MASTER_CPU_IO(myThid)
127
128 C Only do I/O if I am the master thread
129 IF ( iAmDoingIO ) THEN
130
131 C Record number must be >= 1
132 IF (irecord .LT. 1) THEN
133 WRITE(msgBuf,'(A,I9.8)')
134 & ' MDS_READ_FIELD: argument irecord = ',irecord
135 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
136 & SQUEEZE_RIGHT , myThid)
137 WRITE(msgBuf,'(A)')
138 & ' MDS_READ_FIELD: Invalid value for irecord'
139 CALL PRINT_ERROR( msgBuf, myThid )
140 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
141 ENDIF
142 C check for valid sub-set of levels:
143 IF ( kLo.LT.1 .OR. kHi.GT.kSize ) THEN
144 WRITE(msgBuf,'(3(A,I6))')
145 & ' MDS_READ_FIELD: arguments kSize=', kSize,
146 & ' , kLo=', kLo, ' , kHi=', kHi
147 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
148 & SQUEEZE_RIGHT , myThid)
149 WRITE(msgBuf,'(A)')
150 & ' MDS_READ_FIELD: invalid sub-set of levels'
151 CALL PRINT_ERROR( msgBuf, myThid )
152 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
153 ENDIF
154
155 C Assign special directory
156 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
157 pfName= fName
158 ELSE
159 WRITE(pfName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
160 ENDIF
161 pIL=ILNBLNK( pfName )
162
163 C Assign a free unit number as the I/O channel for this routine
164 CALL MDSFINDUNIT( dUnit, myThid )
165
166 C Check first for global file with simple name (ie. fName)
167 dataFName = fName
168 INQUIRE( file=dataFName, exist=exst )
169 IF (exst) THEN
170 IF ( debugLevel .GE. debLevA ) THEN
171 WRITE(msgBuf,'(A,A)')
172 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL)
173 #ifndef ALLOW_ECCO
174 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
175 & SQUEEZE_RIGHT , myThid)
176 #endif
177 ENDIF
178 globalFile = .TRUE.
179 ENDIF
180
181 C If negative check for global file with MDS name (ie. fName.data)
182 IF (.NOT. globalFile) THEN
183 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
184 INQUIRE( file=dataFName, exist=exst )
185 IF (exst) THEN
186 IF ( debugLevel .GE. debLevA ) THEN
187 WRITE(msgBuf,'(A,A)')
188 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL+5)
189 #ifndef ALLOW_ECCO
190 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
191 & SQUEEZE_RIGHT , myThid)
192 #endif
193 ENDIF
194 globalFile = .TRUE.
195 ENDIF
196 ENDIF
197
198 C- endif iAmDoingIO
199 ENDIF
200
201 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
202
203 IF ( useSingleCPUIO ) THEN
204
205 C master thread of process 0, only, opens a global file
206 IF ( iAmDoingIO ) THEN
207 C If global file is visible to process 0, then open it here.
208 C Otherwise stop program.
209 IF ( globalFile) THEN
210 length_of_rec=MDS_RECLEN( filePrec, xSize*ySize, myThid )
211 OPEN( dUnit, file=dataFName, status='old',
212 & access='direct', recl=length_of_rec )
213 ELSE
214 WRITE(msgBuf,'(2A)')
215 & ' MDS_READ_FIELD: filename: ', dataFName(1:IL+5)
216 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
217 & SQUEEZE_RIGHT , myThid)
218 CALL PRINT_ERROR( msgBuf, myThid )
219 WRITE(msgBuf,'(A)')
220 & ' MDS_READ_FIELD: File does not exist'
221 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
222 & SQUEEZE_RIGHT , myThid)
223 CALL PRINT_ERROR( msgBuf, myThid )
224 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
225 ENDIF
226 C- endif iAmDoingIO
227 ENDIF
228
229 DO k=kLo,kHi
230
231 C master thread of process 0, only, read from file
232 IF ( iAmDoingIO ) THEN
233 irec = k+1-kLo+nNz*(irecord-1)
234 IF (filePrec .EQ. precFloat32) THEN
235 READ(dUnit,rec=irec) ( xy_buffer_r4(i),i=1,xSize*ySize )
236 #ifdef _BYTESWAPIO
237 CALL MDS_BYTESWAPR4( xSize*ySize, xy_buffer_r4 )
238 #endif
239 ELSEIF (filePrec .EQ. precFloat64) THEN
240 READ(dUnit,rec=irec) ( xy_buffer_r8(i),i=1,xSize*ySize )
241 #ifdef _BYTESWAPIO
242 CALL MDS_BYTESWAPR8( xSize*ySize, xy_buffer_r8 )
243 #endif
244 ELSE
245 WRITE(msgBuf,'(A)')
246 & ' MDS_READ_FIELD: illegal value for filePrec'
247 CALL PRINT_ERROR( msgBuf, myThid )
248 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
249 ENDIF
250 C- endif iAmDoingIO
251 ENDIF
252
253 IF ( filePrec.EQ.precFloat32 ) THEN
254 CALL SCATTER_2D_R4(
255 U xy_buffer_r4,
256 O sharedLocBuf_r4,
257 I xSize, ySize,
258 I keepBlankTileIO, .FALSE., myThid )
259 IF ( arrType.EQ.'RS' ) THEN
260 CALL MDS_PASS_R4toRS( sharedLocBuf_r4,
261 & arr, k, kSize, .TRUE., myThid )
262 ELSEIF ( arrType.EQ.'RL' ) THEN
263 CALL MDS_PASS_R4toRL( sharedLocBuf_r4,
264 & arr, k, kSize, .TRUE., myThid )
265 ELSE
266 WRITE(msgBuf,'(A)')
267 & ' MDS_READ_FIELD: illegal value for arrType'
268 CALL PRINT_ERROR( msgBuf, myThid )
269 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
270 ENDIF
271 ELSE
272 CALL SCATTER_2D_R8(
273 U xy_buffer_r8,
274 O sharedLocBuf_r8,
275 I xSize, ySize,
276 I keepBlankTileIO, .FALSE., myThid )
277 IF ( arrType.EQ.'RS' ) THEN
278 CALL MDS_PASS_R8toRS( sharedLocBuf_r8,
279 & arr, k, kSize, .TRUE., myThid )
280 ELSEIF ( arrType.EQ.'RL' ) THEN
281 CALL MDS_PASS_R8toRL( sharedLocBuf_r8,
282 & arr, k, kSize, .TRUE., myThid )
283 ELSE
284 WRITE(msgBuf,'(A)')
285 & ' MDS_READ_FIELD: illegal value for arrType'
286 CALL PRINT_ERROR( msgBuf, myThid )
287 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
288 ENDIF
289 ENDIF
290
291 ENDDO
292 c ENDDO k=kLo,kHi
293
294 IF ( iAmDoingIO ) THEN
295 CLOSE( dUnit )
296 ENDIF
297
298 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
299 C--- else .NOT.useSingleCpuIO
300 ELSE
301
302 C Only do I/O if I am the master thread
303 IF ( iAmDoingIO ) THEN
304
305 C If we are reading from a global file then we open it here
306 IF (globalFile) THEN
307 length_of_rec=MDS_RECLEN( filePrec, sNx, myThid )
308 OPEN( dUnit, file=dataFName, status='old',
309 & access='direct', recl=length_of_rec )
310 fileIsOpen=.TRUE.
311 ENDIF
312
313 C Loop over all tiles
314 DO bj=1,nSy
315 DO bi=1,nSx
316 C If we are reading from a tiled MDS file then we open each one here
317 IF (.NOT. globalFile) THEN
318 iG=bi+(myXGlobalLo-1)/sNx ! Kludge until unstructered tiles
319 jG=bj+(myYGlobalLo-1)/sNy ! Kludge until unstructered tiles
320 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
321 & pfName(1:pIL),'.',iG,'.',jG,'.data'
322 INQUIRE( file=dataFName, exist=exst )
323 C Of course, we only open the file if the tile is "active"
324 C (This is a place-holder for the active/passive mechanism
325 IF (exst) THEN
326 IF ( debugLevel .GE. debLevA ) THEN
327 WRITE(msgBuf,'(A,A)')
328 & ' MDS_READ_FIELD: opening file: ',dataFName(1:pIL+13)
329 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
330 & SQUEEZE_RIGHT , myThid)
331 ENDIF
332 length_of_rec=MDS_RECLEN( filePrec, sNx, myThid )
333 OPEN( dUnit, file=dataFName, status='old',
334 & access='direct', recl=length_of_rec )
335 fileIsOpen=.TRUE.
336 ELSE
337 fileIsOpen=.FALSE.
338 WRITE(msgBuf,'(4A)') ' MDS_READ_FIELD: filename: ',
339 & fName(1:IL),' , ', dataFName(1:pIL+13)
340 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
341 & SQUEEZE_RIGHT , myThid)
342 CALL PRINT_ERROR( msgBuf, myThid )
343 WRITE(msgBuf,'(A)')
344 & ' MDS_READ_FIELD: Files DO not exist'
345 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
346 & SQUEEZE_RIGHT , myThid)
347 CALL PRINT_ERROR( msgBuf, myThid )
348 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
349 ENDIF
350 ENDIF
351
352 IF (fileIsOpen) THEN
353 tNy = sNy
354 #ifdef ALLOW_EXCH2
355 tN = W2_myTileList(bi)
356 tGy = exch2_tyGlobalo(tN)
357 tGx = exch2_txGlobalo(tN)
358 tNy = exch2_tNy(tN)
359 tNx = exch2_tNx(tN)
360 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
361 C- face x-size larger than glob-size : fold it
362 iGjLoc = 0
363 jGjLoc = exch2_mydNx(tN) / xSize
364 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
365 C- tile y-size larger than glob-size : make a long line
366 iGjLoc = exch2_mydNx(tN)
367 jGjLoc = 0
368 ELSE
369 C- default (face fit into global-IO-array)
370 iGjLoc = 0
371 jGjLoc = 1
372 ENDIF
373 global_nTx = exch2_global_Nx/tNx
374 #endif /* ALLOW_EXCH2 */
375 DO k=kLo,kHi
376 DO j=1,tNy
377 IF (globalFile) THEN
378 #ifdef ALLOW_EXCH2
379 irec = 1 + ( tGx-1 + (j-1)*iGjLoc )/tNx
380 & + ( tGy-1 + (j-1)*jGjLoc )*global_nTx
381 & + ( k-kLo + (irecord-1)*nNz
382 & )*ySize*global_nTx
383 #else /* ALLOW_EXCH2 */
384 iG = myXGlobalLo-1 + (bi-1)*sNx
385 jG = myYGlobalLo-1 + (bj-1)*sNy
386 irec= 1 + INT(iG/sNx) + nSx*nPx*(jG+j-1)
387 & + nSx*nPx*Ny*(k-kLo)
388 & + nSx*nPx*Ny*nNz*(irecord-1)
389 #endif /* ALLOW_EXCH2 */
390 ELSE
391 irec=j + sNy*(k-kLo) + sNy*nNz*(irecord-1)
392 ENDIF
393 IF (filePrec .EQ. precFloat32) THEN
394 READ(dUnit,rec=irec) r4seg
395 #ifdef _BYTESWAPIO
396 CALL MDS_BYTESWAPR4( sNx, r4seg )
397 #endif
398 IF (arrType .EQ. 'RS') THEN
399 CALL MDS_SEG4toRS( j,bi,bj,k,kSize, r4seg, .TRUE., arr )
400 ELSEIF (arrType .EQ. 'RL') THEN
401 CALL MDS_SEG4toRL( j,bi,bj,k,kSize, r4seg, .TRUE., arr )
402 ELSE
403 WRITE(msgBuf,'(A)')
404 & ' MDS_READ_FIELD: illegal value for arrType'
405 CALL PRINT_ERROR( msgBuf, myThid )
406 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
407 ENDIF
408 ELSEIF (filePrec .EQ. precFloat64) THEN
409 READ(dUnit,rec=irec) r8seg
410 #ifdef _BYTESWAPIO
411 CALL MDS_BYTESWAPR8( sNx, r8seg )
412 #endif
413 IF (arrType .EQ. 'RS') THEN
414 CALL MDS_SEG8toRS( j,bi,bj,k,kSize, r8seg, .TRUE., arr )
415 ELSEIF (arrType .EQ. 'RL') THEN
416 CALL MDS_SEG8toRL( j,bi,bj,k,kSize, r8seg, .TRUE., arr )
417 ELSE
418 WRITE(msgBuf,'(A)')
419 & ' MDS_READ_FIELD: illegal value for arrType'
420 CALL PRINT_ERROR( msgBuf, myThid )
421 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
422 ENDIF
423 ELSE
424 WRITE(msgBuf,'(A)')
425 & ' MDS_READ_FIELD: illegal value for filePrec'
426 CALL PRINT_ERROR( msgBuf, myThid )
427 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
428 ENDIF
429 C End of j loop
430 ENDDO
431 C End of k loop
432 ENDDO
433 C end if fileIsOpen
434 ENDIF
435 IF (fileIsOpen .AND. (.NOT. globalFile)) THEN
436 CLOSE( dUnit )
437 fileIsOpen = .FALSE.
438 ENDIF
439 C End of bi,bj loops
440 ENDDO
441 ENDDO
442
443 C If global file was opened then close it
444 IF (fileIsOpen .AND. globalFile) THEN
445 CLOSE( dUnit )
446 fileIsOpen = .FALSE.
447 ENDIF
448
449 C- endif iAmDoingIO
450 ENDIF
451
452 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
453 C if useSingleCpuIO / else / end
454 ENDIF
455
456 RETURN
457 END

  ViewVC Help
Powered by ViewVC 1.1.22