/[MITgcm]/MITgcm_contrib/llc_hires/llc_1080/code-async/mdsio_read_field.F
ViewVC logotype

Contents of /MITgcm_contrib/llc_hires/llc_1080/code-async/mdsio_read_field.F

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


Revision 1.3 - (show annotations) (download)
Sat Mar 2 19:31:13 2019 UTC (6 years, 5 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
Changes since 1.2: +7 -1 lines
updated asyncio code from Bron Nelson, which can now be use to read pickup files

1 C $Header: /u/gcmpack/MITgcm_contrib/llc_hires/llc_1080/code-async/mdsio_read_field.F,v 1.2 2019/02/27 20:56:33 dimitri 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 fldRL, fldRS,
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)) :: which array (fldRL/RS) to read into, either "RL" or "RS"
27 C kSize (integer) :: size of third dimension: normally either 1 or Nr
28 C kLo (integer) :: 1rst vertical level (of array fldRL/RS) to read-in
29 C kHi (integer) :: last vertical level (of array fldRL/RS) to read-in
30 C fldRL ( RL ) :: array to read into if arrType="RL", fldRL(:,:,kSize,:,:)
31 C fldRS ( RS ) :: array to read into if arrType="RS", fldRS(:,:,kSize,:,:)
32 C irecord (integer) :: record number to read
33 C myIter (integer) :: time step number
34 C myThid (integer) :: thread identifier
35 C
36 C MDS_READ_FIELD first checks to see IF the file "fName" exists, then
37 C IF the file "fName.data" exists and finally the tiled files of the
38 C form "fName.xxx.yyy.data" exist. Currently, the meta-files are not
39 C read because it is difficult to parse files in fortran.
40 C The precision of the file is decsribed by filePrec, set either
41 C to floatPrec32 or floatPrec64. The char*(2) string arrType, either "RL"
42 C or "RS", selects which array is filled in, either fldRL or fldRS.
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 fldRL/RS *but* the overlaps are *not* updated,
49 C i.e., an exchange must be called.
50 C
51 C- Multi-threaded: Only Master thread does IO (and MPI calls) and put data
52 C to a shared buffer that any thread can get access to.
53 C- Convention regarding thread synchronisation (BARRIER):
54 C A per-thread (or per tile) partition of the 2-D shared-buffer (sharedLocBuf_r4/r8)
55 C is readily available => any access (e.g., by master-thread) to a portion
56 C owned by an other thread is put between BARRIER (protected).
57 C No thread partition exist for the 3-D shared buffer (shared3dBuf_r4/r8).
58 C Therefore, the 3-D buffer is considered to be owned by master-thread and
59 C any access by other than master thread is put between BARRIER (protected).
60 C
61 C Created: 03/16/99 adcroft@mit.edu
62 CEOP
63
64 C !USES:
65 IMPLICIT NONE
66 C Global variables / common blocks
67 #include "SIZE.h"
68 #include "EEPARAMS.h"
69 #include "EESUPPORT.h"
70 #include "PARAMS.h"
71 #ifdef ALLOW_EXCH2
72 #include "W2_EXCH2_SIZE.h"
73 #include "W2_EXCH2_TOPOLOGY.h"
74 #include "W2_EXCH2_PARAMS.h"
75 #endif /* ALLOW_EXCH2 */
76 #include "EEBUFF_SCPU.h"
77 #ifdef ALLOW_FIZHI
78 # include "fizhi_SIZE.h"
79 #endif /* ALLOW_FIZHI */
80 #include "MDSIO_BUFF_3D.h"
81
82 C !INPUT PARAMETERS:
83 CHARACTER*(*) fName
84 INTEGER filePrec
85 LOGICAL useCurrentDir
86 CHARACTER*(2) arrType
87 INTEGER kSize, kLo, kHi
88 INTEGER irecord
89 INTEGER myThid
90 C !OUTPUT PARAMETERS:
91 _RL fldRL(*)
92 _RS fldRS(*)
93
94 C !FUNCTIONS
95 INTEGER ILNBLNK
96 INTEGER MDS_RECLEN
97 LOGICAL MASTER_CPU_IO
98 EXTERNAL ILNBLNK
99 EXTERNAL MDS_RECLEN
100 EXTERNAL MASTER_CPU_IO
101
102 C !LOCAL VARIABLES:
103 C bBij :: base shift in Buffer index for tile bi,bj
104 CHARACTER*(MAX_LEN_FNAM) dataFName,pfName
105 CHARACTER*(MAX_LEN_MBUF) msgBuf
106 LOGICAL exst
107 LOGICAL globalFile, fileIsOpen
108 LOGICAL iAmDoingIO
109 LOGICAL useExch2ioLayOut
110 INTEGER xSize, ySize
111 INTEGER iG,jG,bi,bj
112 INTEGER i1,i2,i,j,k,nNz
113 INTEGER irec,dUnit,IL,pIL
114 INTEGER length_of_rec
115 INTEGER bBij
116 INTEGER tNx, tNy, global_nTx
117 INTEGER tBx, tBy, iGjLoc, jGjLoc
118 #ifdef ALLOW_EXCH2
119 INTEGER tN
120 #endif /* ALLOW_EXCH2 */
121
122 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
123 C Set dimensions:
124 xSize = Nx
125 ySize = Ny
126 useExch2ioLayOut = .FALSE.
127 #ifdef ALLOW_EXCH2
128 IF ( W2_useE2ioLayOut ) THEN
129 xSize = exch2_global_Nx
130 ySize = exch2_global_Ny
131 useExch2ioLayOut = .TRUE.
132 ENDIF
133 #endif /* ALLOW_EXCH2 */
134
135 C Assume nothing
136 globalFile = .FALSE.
137 fileIsOpen = .FALSE.
138 IL = ILNBLNK( fName )
139 pIL = ILNBLNK( mdsioLocalDir )
140 nNz = 1 + kHi - kLo
141
142 C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO):
143 iAmDoingIO = MASTER_CPU_IO(myThid)
144
145 C File name should not be too long:
146 C IL(+pIL if not useCurrentDir)(+5: '.data')(+8: bi,bj) =< MAX_LEN_FNAM
147 C and shorter enough to be written to msgBuf with other informations
148 IF ( useCurrentDir .AND. (90+IL).GT.MAX_LEN_MBUF ) THEN
149 WRITE(msgBuf,'(2A,2(I4,A))') 'MDS_READ_FIELD: ',
150 & 'Too long (IL=',IL,') file name:'
151 CALL PRINT_ERROR( msgBuf, myThid )
152 WRITE(errorMessageUnit,'(3A)')'file: >',fName(1:IL),'<'
153 CALL ALL_PROC_DIE( myThid )
154 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
155 ELSEIF ( (90+IL+pIL).GT.MAX_LEN_MBUF ) THEN
156 WRITE(msgBuf,'(2A,2(I4,A))') 'MDS_READ_FIELD: ',
157 & 'Too long (pIL=',pIL,', IL=',IL,') pfix + file name:'
158 CALL PRINT_ERROR( msgBuf, myThid )
159 WRITE(errorMessageUnit,'(3A)')'pfix: >',mdsioLocalDir(1:pIL),'<'
160 WRITE(errorMessageUnit,'(3A)')'file: >',fName(1:IL),'<'
161 CALL ALL_PROC_DIE( myThid )
162 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
163 ENDIF
164 C Record number must be >= 1
165 IF (irecord .LT. 1) THEN
166 WRITE(msgBuf,'(3A,I10)')
167 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
168 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
169 & SQUEEZE_RIGHT, myThid )
170 WRITE(msgBuf,'(A,I9.8)')
171 & ' MDS_READ_FIELD: argument irecord = ',irecord
172 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
173 & SQUEEZE_RIGHT, myThid )
174 WRITE(msgBuf,'(A)')
175 & ' MDS_READ_FIELD: Invalid value for irecord'
176 CALL PRINT_ERROR( msgBuf, myThid )
177 CALL ALL_PROC_DIE( myThid )
178 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
179 ENDIF
180 C check for valid sub-set of levels:
181 IF ( kLo.LT.1 .OR. kHi.GT.kSize ) THEN
182 WRITE(msgBuf,'(3A,I10)')
183 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
184 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
185 & SQUEEZE_RIGHT, myThid )
186 WRITE(msgBuf,'(3(A,I6))')
187 & ' MDS_READ_FIELD: arguments kSize=', kSize,
188 & ' , kLo=', kLo, ' , kHi=', kHi
189 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
190 & SQUEEZE_RIGHT, myThid )
191 WRITE(msgBuf,'(A)')
192 & ' MDS_READ_FIELD: invalid sub-set of levels'
193 CALL PRINT_ERROR( msgBuf, myThid )
194 CALL ALL_PROC_DIE( myThid )
195 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
196 ENDIF
197 C check for 3-D Buffer size:
198 IF ( .NOT.useSingleCpuIO .AND. nNz.GT.size3dBuf ) THEN
199 WRITE(msgBuf,'(3A,I10)')
200 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
201 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
202 & SQUEEZE_RIGHT, myThid )
203 WRITE(msgBuf,'(3(A,I6))')
204 & ' MDS_READ_FIELD: Nb Lev to read =', nNz,
205 & ' >', size3dBuf, ' = buffer 3rd Dim'
206 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
207 & SQUEEZE_RIGHT, myThid )
208 WRITE(msgBuf,'(A)')
209 & ' MDS_READ_FIELD: buffer 3rd Dim. too small'
210 CALL PRINT_ERROR( msgBuf, myThid )
211 WRITE(msgBuf,'(A)')
212 & ' increase "size3dBuf" in "MDSIO_BUFF_3D.h" and recompile'
213 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
214 & SQUEEZE_RIGHT, myThid )
215 CALL ALL_PROC_DIE( myThid )
216 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
217 ENDIF
218
219 C Only do I/O if I am the master thread
220 IF ( iAmDoingIO ) THEN
221
222 C Assign special directory
223 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
224 pfName= fName
225 ELSE
226 WRITE(pfName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
227 ENDIF
228 pIL=ILNBLNK( pfName )
229
230 C Assign a free unit number as the I/O channel for this routine
231 CALL MDSFINDUNIT( dUnit, myThid )
232
233 C Check first for global file with simple name (ie. fName)
234 dataFName = fName
235 INQUIRE( file=dataFName, exist=exst )
236 IF (exst) THEN
237 IF ( debugLevel .GE. debLevB ) THEN
238 WRITE(msgBuf,'(A,A)')
239 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL)
240 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
241 & SQUEEZE_RIGHT, myThid)
242 ENDIF
243 globalFile = .TRUE.
244 ENDIF
245
246 C If negative check for global file with MDS name (ie. fName.data)
247 IF (.NOT. globalFile) THEN
248 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
249 INQUIRE( file=dataFName, exist=exst )
250 IF (exst) THEN
251 IF ( debugLevel .GE. debLevB ) THEN
252 WRITE(msgBuf,'(A,A)')
253 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL+5)
254 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
255 & SQUEEZE_RIGHT, myThid)
256 ENDIF
257 globalFile = .TRUE.
258 ENDIF
259 ENDIF
260
261 C- endif iAmDoingIO
262 ENDIF
263
264 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
265
266 IF ( useSingleCPUIO ) THEN
267
268 C master thread of process 0, only, opens a global file
269 IF ( iAmDoingIO ) THEN
270 C If global file is visible to process 0, then open it here.
271 C Otherwise stop program.
272 IF ( globalFile) THEN
273 length_of_rec = MDS_RECLEN( filePrec, xSize*ySize, myThid )
274 OPEN( dUnit, file=dataFName, status='old',
275 & access='direct', recl=length_of_rec )
276 ELSE
277 WRITE(msgBuf,'(2A)')
278 & ' MDS_READ_FIELD: filename: ', dataFName(1:IL+5)
279 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
280 & SQUEEZE_RIGHT, myThid)
281 CALL PRINT_ERROR( msgBuf, myThid )
282 WRITE(msgBuf,'(A)')
283 & ' MDS_READ_FIELD: File does not exist'
284 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
285 & SQUEEZE_RIGHT, myThid)
286 CALL PRINT_ERROR( msgBuf, myThid )
287 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
288 ENDIF
289 C- endif iAmDoingIO
290 ENDIF
291
292 DO k=kLo,kHi
293
294 C master thread of process 0, only, read from file
295 IF ( iAmDoingIO ) THEN
296 irec = 1 + k-kLo + (irecord-1)*nNz
297 IF (filePrec .EQ. precFloat32) THEN
298 READ(dUnit,rec=irec) ( xy_buffer_r4(i),i=1,xSize*ySize )
299 #ifdef _BYTESWAPIO
300 CALL MDS_BYTESWAPR4( xSize*ySize, xy_buffer_r4 )
301 #endif
302 ELSE
303 READ(dUnit,rec=irec) ( xy_buffer_r8(i),i=1,xSize*ySize )
304 #ifdef _BYTESWAPIO
305 CALL MDS_BYTESWAPR8( xSize*ySize, xy_buffer_r8 )
306 #endif
307 ENDIF
308 C- endif iAmDoingIO
309 ENDIF
310
311 C Wait for all thread to finish. This prevents other threads to continue
312 C to acces shared buffer while master thread is loading data into
313 CALL BAR2( myThid )
314
315 IF ( filePrec.EQ.precFloat32 ) THEN
316 CALL SCATTER_2D_R4(
317 U xy_buffer_r4,
318 O sharedLocBuf_r4,
319 I xSize, ySize,
320 I useExch2ioLayOut, .FALSE., myThid )
321 C All threads wait for Master to finish loading into shared buffer
322 CALL BAR2( myThid )
323 IF ( arrType.EQ.'RS' ) THEN
324 CALL MDS_PASS_R4toRS( sharedLocBuf_r4, fldRS,
325 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
326 ELSEIF ( arrType.EQ.'RL' ) THEN
327 CALL MDS_PASS_R4toRL( sharedLocBuf_r4, fldRL,
328 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
329 ELSE
330 WRITE(msgBuf,'(A)')
331 & ' MDS_READ_FIELD: illegal value for arrType'
332 CALL PRINT_ERROR( msgBuf, myThid )
333 CALL ALL_PROC_DIE( myThid )
334 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
335 ENDIF
336 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
337 CALL SCATTER_2D_R8(
338 U xy_buffer_r8,
339 O sharedLocBuf_r8,
340 I xSize, ySize,
341 I useExch2ioLayOut, .FALSE., myThid )
342 C All threads wait for Master to finish loading into shared buffer
343 CALL BAR2( myThid )
344 IF ( arrType.EQ.'RS' ) THEN
345 CALL MDS_PASS_R8toRS( sharedLocBuf_r8, fldRS,
346 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
347 ELSEIF ( arrType.EQ.'RL' ) THEN
348 CALL MDS_PASS_R8toRL( sharedLocBuf_r8, fldRL,
349 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
350 ELSE
351 WRITE(msgBuf,'(A)')
352 & ' MDS_READ_FIELD: illegal value for arrType'
353 CALL PRINT_ERROR( msgBuf, myThid )
354 CALL ALL_PROC_DIE( myThid )
355 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
356 ENDIF
357 ELSE
358 WRITE(msgBuf,'(A)')
359 & ' MDS_READ_FIELD: illegal value for filePrec'
360 CALL PRINT_ERROR( msgBuf, myThid )
361 CALL ALL_PROC_DIE( myThid )
362 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
363 ENDIF
364
365 ENDDO
366 c ENDDO k=kLo,kHi
367
368 IF ( iAmDoingIO ) THEN
369 CLOSE( dUnit )
370 ENDIF
371
372 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
373 C--- else .NOT.useSingleCpuIO
374 ELSE
375
376 C Wait for all thread to finish. This prevents other threads to continue
377 C to acces 3-D buffer while master thread is reading
378 c CALL BAR2( myThid )
379
380 C Only do I/O if I am the master thread
381 IF ( iAmDoingIO ) THEN
382
383 C If we are reading from a global file then we open it here
384 IF (globalFile) THEN
385 length_of_rec = MDS_RECLEN( filePrec, sNx, myThid )
386 OPEN( dUnit, file=dataFName, status='old',
387 & access='direct', recl=length_of_rec )
388 fileIsOpen=.TRUE.
389 ENDIF
390
391 C Loop over all tiles
392 DO bj=1,nSy
393 DO bi=1,nSx
394 bBij = sNx*sNy*nNz*( bi-1 + (bj-1)*nSx )
395
396 IF (globalFile) THEN
397 C--- Case of 1 Global file:
398
399 c IF (fileIsOpen) THEN
400 tNx = sNx
401 tNy = sNy
402 global_nTx = xSize/sNx
403 tBx = myXGlobalLo-1 + (bi-1)*sNx
404 tBy = myYGlobalLo-1 + (bj-1)*sNy
405 iGjLoc = 0
406 jGjLoc = 1
407 #ifdef ALLOW_EXCH2
408 IF ( useExch2ioLayOut ) THEN
409 tN = W2_myTileList(bi,bj)
410 c tNx = exch2_tNx(tN)
411 c tNy = exch2_tNy(tN)
412 c global_nTx = exch2_global_Nx/tNx
413 tBx = exch2_txGlobalo(tN) - 1
414 tBy = exch2_tyGlobalo(tN) - 1
415 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
416 C- face x-size larger than glob-size : fold it
417 iGjLoc = 0
418 jGjLoc = exch2_mydNx(tN) / xSize
419 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
420 C- tile y-size larger than glob-size : make a long line
421 iGjLoc = exch2_mydNx(tN)
422 jGjLoc = 0
423 ELSE
424 C- default (face fit into global-IO-array)
425 iGjLoc = 0
426 jGjLoc = 1
427 ENDIF
428 ENDIF
429 #endif /* ALLOW_EXCH2 */
430
431
432
433
434
435 chenze : Our mpi-i/o-based routines don't yet support 32-bit elements
436 chenze : so we are routing those through the standard i/o mechanism.
437 chenze : Also, we're assuming that byte-swapping of the usual bigendian
438 chenze : files is done via Fortran i/o. Our C routines will not do this,
439 chenze : so we swap explicitly here. If _BYTESWAPIO is set, this will break.
440
441 #ifdef ALLOW_ASYNCIO
442 ! WRITE (msgBuf, '(A)') ' use NEW readField'
443 ! CALL PRINT_ERROR ( msgBuf, myThid )
444
445 IF ( filePrec.EQ.precFloat64 ) then
446
447 irec = (irecord-1)*nNz*global_nTx*ySize
448
449 call readField(MPI_COMM_MODEL, dataFName,
450 & irec,
451 & shared3dBuf_r8, tN, nNz)
452
453
454 CALL MDS_BYTESWAPR8( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r8 )
455
456 else
457 #endif
458
459 ! WRITE (msgBuf, '(A)') ' use OLD readField'
460 ! CALL PRINT_ERROR ( msgBuf, myThid )
461
462 DO k=kLo,kHi
463 DO j=1,tNy
464 irec = 1 + ( tBx + (j-1)*iGjLoc )/sNx
465 & + ( tBy + (j-1)*jGjLoc )*global_nTx
466 & +( k-kLo + (irecord-1)*nNz )*global_nTx*ySize
467 i1 = bBij + 1 + (j-1)*sNx + (k-kLo)*sNx*sNy
468 i2 = bBij + j*sNx + (k-kLo)*sNx*sNy
469 IF ( filePrec.EQ.precFloat32 ) THEN
470 READ(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
471 ELSE
472 READ(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
473 ENDIF
474 C End of j,k loops
475 ENDDO
476 ENDDO
477
478 #ifdef ALLOW_ASYNCIO
479 endif
480 #endif
481
482
483
484
485 C end if fileIsOpen
486 c ENDIF
487
488 ELSE
489 C--- Case of 1 file per tile (globalFile=F):
490
491 C If we are reading from a tiled MDS file then we open each one here
492 iG=bi+(myXGlobalLo-1)/sNx
493 jG=bj+(myYGlobalLo-1)/sNy
494 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
495 & pfName(1:pIL),'.',iG,'.',jG,'.data'
496 INQUIRE( file=dataFName, exist=exst )
497 C Of course, we only open the file if the tile is "active"
498 C (This is a place-holder for the active/passive mechanism
499 IF (exst) THEN
500 IF ( debugLevel .GE. debLevB ) THEN
501 WRITE(msgBuf,'(A,A)')
502 & ' MDS_READ_FIELD: opening file: ',dataFName(1:pIL+13)
503 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
504 & SQUEEZE_RIGHT, myThid)
505 ENDIF
506 length_of_rec = MDS_RECLEN( filePrec, sNx*sNy*nNz, myThid )
507 OPEN( dUnit, file=dataFName, status='old',
508 & access='direct', recl=length_of_rec )
509 fileIsOpen=.TRUE.
510 ELSE
511 fileIsOpen=.FALSE.
512 WRITE(msgBuf,'(4A)') ' MDS_READ_FIELD: filename: ',
513 & fName(1:IL),' , ', dataFName(1:pIL+13)
514 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
515 & SQUEEZE_RIGHT, myThid)
516 CALL PRINT_ERROR( msgBuf, myThid )
517 WRITE(msgBuf,'(A)')
518 & ' MDS_READ_FIELD: Files DO not exist'
519 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
520 & SQUEEZE_RIGHT, myThid)
521 CALL PRINT_ERROR( msgBuf, myThid )
522 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
523 ENDIF
524
525 irec = irecord
526 i1 = bBij + 1
527 i2 = bBij + sNx*sNy*nNz
528 IF ( filePrec.EQ.precFloat32 ) THEN
529 READ(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
530 ELSE
531 READ(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
532 ENDIF
533
534 C here We close the tiled MDS file
535 IF ( fileIsOpen ) THEN
536 CLOSE( dUnit )
537 fileIsOpen = .FALSE.
538 ENDIF
539
540 C--- End Global File / tile-file cases
541 ENDIF
542
543 C End of bi,bj loops
544 ENDDO
545 ENDDO
546
547 C If global file was opened then close it
548 IF (fileIsOpen .AND. globalFile) THEN
549 CLOSE( dUnit )
550 fileIsOpen = .FALSE.
551 ENDIF
552
553 #ifdef _BYTESWAPIO
554 IF ( filePrec.EQ.precFloat32 ) THEN
555 CALL MDS_BYTESWAPR4( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r4 )
556 ELSE
557 CALL MDS_BYTESWAPR8( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r8 )
558 ENDIF
559 #endif
560
561 C- endif iAmDoingIO
562 ENDIF
563
564 C All threads wait for Master to finish reading into shared buffer
565 CALL BAR2( myThid )
566
567 C--- Copy from 3-D buffer to fldRL/RS (multi-threads):
568 IF ( filePrec.EQ.precFloat32 ) THEN
569 IF ( arrType.EQ.'RS' ) THEN
570 CALL MDS_PASS_R4toRS( shared3dBuf_r4, fldRS,
571 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
572 ELSEIF ( arrType.EQ.'RL' ) THEN
573 CALL MDS_PASS_R4toRL( shared3dBuf_r4, fldRL,
574 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
575 ELSE
576 WRITE(msgBuf,'(A)')
577 & ' MDS_READ_FIELD: illegal value for arrType'
578 CALL PRINT_ERROR( msgBuf, myThid )
579 CALL ALL_PROC_DIE( myThid )
580 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
581 ENDIF
582 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
583 IF ( arrType.EQ.'RS' ) THEN
584 CALL MDS_PASS_R8toRS( shared3dBuf_r8, fldRS,
585 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
586 ELSEIF ( arrType.EQ.'RL' ) THEN
587 CALL MDS_PASS_R8toRL( shared3dBuf_r8, fldRL,
588 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
589 ELSE
590 WRITE(msgBuf,'(A)')
591 & ' MDS_READ_FIELD: illegal value for arrType'
592 CALL PRINT_ERROR( msgBuf, myThid )
593 CALL ALL_PROC_DIE( myThid )
594 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
595 ENDIF
596 ELSE
597 WRITE(msgBuf,'(A)')
598 & ' MDS_READ_FIELD: illegal value for filePrec'
599 CALL PRINT_ERROR( msgBuf, myThid )
600 CALL ALL_PROC_DIE( myThid )
601 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
602 ENDIF
603
604 C Wait for all threads to finish getting data from 3-D shared buffer.
605 C This prevents the master-thread to change the buffer content before
606 C every one got his data.
607 CALL BAR2( myThid )
608
609 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
610 C if useSingleCpuIO / else / end
611 ENDIF
612
613 RETURN
614 END

  ViewVC Help
Powered by ViewVC 1.1.22