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

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

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


Revision 1.1 - (show annotations) (download)
Fri Sep 20 12:38:03 2013 UTC (11 years, 10 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
adding llc_2160 and llc_4320 coonfiguration files

1 C $Header: /CVS/people/chenze/ECCO/code-async/mdsio_read_field.F,v 1.3 2013/09/16 22:03:11 chenze 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 Record number must be >= 1
146 IF (irecord .LT. 1) THEN
147 WRITE(msgBuf,'(3A,I10)')
148 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
149 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
150 & SQUEEZE_RIGHT , myThid )
151 WRITE(msgBuf,'(A,I9.8)')
152 & ' MDS_READ_FIELD: argument irecord = ',irecord
153 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
154 & SQUEEZE_RIGHT , myThid )
155 WRITE(msgBuf,'(A)')
156 & ' MDS_READ_FIELD: Invalid value for irecord'
157 CALL PRINT_ERROR( msgBuf, myThid )
158 CALL ALL_PROC_DIE( myThid )
159 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
160 ENDIF
161 C check for valid sub-set of levels:
162 IF ( kLo.LT.1 .OR. kHi.GT.kSize ) THEN
163 WRITE(msgBuf,'(3A,I10)')
164 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
165 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
166 & SQUEEZE_RIGHT , myThid )
167 WRITE(msgBuf,'(3(A,I6))')
168 & ' MDS_READ_FIELD: arguments kSize=', kSize,
169 & ' , kLo=', kLo, ' , kHi=', kHi
170 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
171 & SQUEEZE_RIGHT , myThid )
172 WRITE(msgBuf,'(A)')
173 & ' MDS_READ_FIELD: invalid sub-set of levels'
174 CALL PRINT_ERROR( msgBuf, myThid )
175 CALL ALL_PROC_DIE( myThid )
176 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
177 ENDIF
178 C check for 3-D Buffer size:
179 IF ( .NOT.useSingleCpuIO .AND. nNz.GT.size3dBuf ) THEN
180 WRITE(msgBuf,'(3A,I10)')
181 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
182 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
183 & SQUEEZE_RIGHT , myThid )
184 WRITE(msgBuf,'(3(A,I6))')
185 & ' MDS_READ_FIELD: Nb Lev to read =', nNz,
186 & ' >', size3dBuf, ' = buffer 3rd Dim'
187 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
188 & SQUEEZE_RIGHT , myThid )
189 WRITE(msgBuf,'(A)')
190 & ' MDS_READ_FIELD: buffer 3rd Dim. too small'
191 CALL PRINT_ERROR( msgBuf, myThid )
192 WRITE(msgBuf,'(A)')
193 & ' increase "size3dBuf" in "MDSIO_BUFF_3D.h" and recompile'
194 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
195 & SQUEEZE_RIGHT , myThid )
196 CALL ALL_PROC_DIE( myThid )
197 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
198 ENDIF
199
200 C Only do I/O if I am the master thread
201 IF ( iAmDoingIO ) THEN
202
203 C Assign special directory
204 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
205 pfName= fName
206 ELSE
207 WRITE(pfName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
208 ENDIF
209 pIL=ILNBLNK( pfName )
210
211 C Assign a free unit number as the I/O channel for this routine
212 CALL MDSFINDUNIT( dUnit, myThid )
213
214 C Check first for global file with simple name (ie. fName)
215 dataFName = fName
216 INQUIRE( file=dataFName, exist=exst )
217 IF (exst) THEN
218 IF ( debugLevel .GE. debLevB ) THEN
219 WRITE(msgBuf,'(A,A)')
220 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL)
221 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
222 & SQUEEZE_RIGHT , myThid)
223 ENDIF
224 globalFile = .TRUE.
225 ENDIF
226
227 C If negative check for global file with MDS name (ie. fName.data)
228 IF (.NOT. globalFile) THEN
229 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
230 INQUIRE( file=dataFName, exist=exst )
231 IF (exst) THEN
232 IF ( debugLevel .GE. debLevB ) THEN
233 WRITE(msgBuf,'(A,A)')
234 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL+5)
235 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
236 & SQUEEZE_RIGHT , myThid)
237 ENDIF
238 globalFile = .TRUE.
239 ENDIF
240 ENDIF
241
242 C- endif iAmDoingIO
243 ENDIF
244
245 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
246
247 IF ( useSingleCPUIO ) THEN
248
249 C master thread of process 0, only, opens a global file
250 IF ( iAmDoingIO ) THEN
251 C If global file is visible to process 0, then open it here.
252 C Otherwise stop program.
253 IF ( globalFile) THEN
254 length_of_rec = MDS_RECLEN( filePrec, xSize*ySize, myThid )
255 OPEN( dUnit, file=dataFName, status='old',
256 & access='direct', recl=length_of_rec )
257 ELSE
258 WRITE(msgBuf,'(2A)')
259 & ' MDS_READ_FIELD: filename: ', dataFName(1:IL+5)
260 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
261 & SQUEEZE_RIGHT , myThid)
262 CALL PRINT_ERROR( msgBuf, myThid )
263 WRITE(msgBuf,'(A)')
264 & ' MDS_READ_FIELD: File does not exist'
265 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
266 & SQUEEZE_RIGHT , myThid)
267 CALL PRINT_ERROR( msgBuf, myThid )
268 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
269 ENDIF
270 C- endif iAmDoingIO
271 ENDIF
272
273 DO k=kLo,kHi
274
275 C master thread of process 0, only, read from file
276 IF ( iAmDoingIO ) THEN
277 irec = 1 + k-kLo + (irecord-1)*nNz
278 IF (filePrec .EQ. precFloat32) THEN
279 READ(dUnit,rec=irec) ( xy_buffer_r4(i),i=1,xSize*ySize )
280 #ifdef _BYTESWAPIO
281 CALL MDS_BYTESWAPR4( xSize*ySize, xy_buffer_r4 )
282 #endif
283 ELSE
284 READ(dUnit,rec=irec) ( xy_buffer_r8(i),i=1,xSize*ySize )
285 #ifdef _BYTESWAPIO
286 CALL MDS_BYTESWAPR8( xSize*ySize, xy_buffer_r8 )
287 #endif
288 ENDIF
289 C- endif iAmDoingIO
290 ENDIF
291
292 C Wait for all thread to finish. This prevents other threads to continue
293 C to acces shared buffer while master thread is loading data into
294 CALL BAR2( myThid )
295
296 IF ( filePrec.EQ.precFloat32 ) THEN
297 CALL SCATTER_2D_R4(
298 U xy_buffer_r4,
299 O sharedLocBuf_r4,
300 I xSize, ySize,
301 I useExch2ioLayOut, .FALSE., myThid )
302 C All threads wait for Master to finish loading into shared buffer
303 CALL BAR2( myThid )
304 IF ( arrType.EQ.'RS' ) THEN
305 CALL MDS_PASS_R4toRS( sharedLocBuf_r4, fldRS,
306 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
307 ELSEIF ( arrType.EQ.'RL' ) THEN
308 CALL MDS_PASS_R4toRL( sharedLocBuf_r4, fldRL,
309 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
310 ELSE
311 WRITE(msgBuf,'(A)')
312 & ' MDS_READ_FIELD: illegal value for arrType'
313 CALL PRINT_ERROR( msgBuf, myThid )
314 CALL ALL_PROC_DIE( myThid )
315 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
316 ENDIF
317 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
318 CALL SCATTER_2D_R8(
319 U xy_buffer_r8,
320 O sharedLocBuf_r8,
321 I xSize, ySize,
322 I useExch2ioLayOut, .FALSE., myThid )
323 C All threads wait for Master to finish loading into shared buffer
324 CALL BAR2( myThid )
325 IF ( arrType.EQ.'RS' ) THEN
326 CALL MDS_PASS_R8toRS( sharedLocBuf_r8, fldRS,
327 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
328 ELSEIF ( arrType.EQ.'RL' ) THEN
329 CALL MDS_PASS_R8toRL( sharedLocBuf_r8, fldRL,
330 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
331 ELSE
332 WRITE(msgBuf,'(A)')
333 & ' MDS_READ_FIELD: illegal value for arrType'
334 CALL PRINT_ERROR( msgBuf, myThid )
335 CALL ALL_PROC_DIE( myThid )
336 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
337 ENDIF
338 ELSE
339 WRITE(msgBuf,'(A)')
340 & ' MDS_READ_FIELD: illegal value for filePrec'
341 CALL PRINT_ERROR( msgBuf, myThid )
342 CALL ALL_PROC_DIE( myThid )
343 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
344 ENDIF
345
346 ENDDO
347 c ENDDO k=kLo,kHi
348
349 IF ( iAmDoingIO ) THEN
350 CLOSE( dUnit )
351 ENDIF
352
353 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
354 C--- else .NOT.useSingleCpuIO
355 ELSE
356
357 C Wait for all thread to finish. This prevents other threads to continue
358 C to acces 3-D buffer while master thread is reading
359 c CALL BAR2( myThid )
360
361 C Only do I/O if I am the master thread
362 IF ( iAmDoingIO ) THEN
363
364 C If we are reading from a global file then we open it here
365 IF (globalFile) THEN
366 length_of_rec = MDS_RECLEN( filePrec, sNx, myThid )
367 OPEN( dUnit, file=dataFName, status='old',
368 & access='direct', recl=length_of_rec )
369 fileIsOpen=.TRUE.
370 ENDIF
371
372 C Loop over all tiles
373 DO bj=1,nSy
374 DO bi=1,nSx
375 bBij = sNx*sNy*nNz*( bi-1 + (bj-1)*nSx )
376
377 IF (globalFile) THEN
378 C--- Case of 1 Global file:
379
380 c IF (fileIsOpen) THEN
381 tNx = sNx
382 tNy = sNy
383 global_nTx = xSize/sNx
384 tBx = myXGlobalLo-1 + (bi-1)*sNx
385 tBy = myYGlobalLo-1 + (bj-1)*sNy
386 iGjLoc = 0
387 jGjLoc = 1
388 #ifdef ALLOW_EXCH2
389 IF ( useExch2ioLayOut ) THEN
390 tN = W2_myTileList(bi,bj)
391 c tNx = exch2_tNx(tN)
392 c tNy = exch2_tNy(tN)
393 c global_nTx = exch2_global_Nx/tNx
394 tBx = exch2_txGlobalo(tN) - 1
395 tBy = exch2_tyGlobalo(tN) - 1
396 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
397 C- face x-size larger than glob-size : fold it
398 iGjLoc = 0
399 jGjLoc = exch2_mydNx(tN) / xSize
400 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
401 C- tile y-size larger than glob-size : make a long line
402 iGjLoc = exch2_mydNx(tN)
403 jGjLoc = 0
404 ELSE
405 C- default (face fit into global-IO-array)
406 iGjLoc = 0
407 jGjLoc = 1
408 ENDIF
409 ENDIF
410 #endif /* ALLOW_EXCH2 */
411
412
413
414
415
416 chenze : Our mpi-i/o-based routines don't yet support 32-bit elements
417 chenze : so we are routing those through the standard i/o mechanism.
418 chenze : Also, we're assuming that byte-swapping of the usual bigendian
419 chenze : files is done via Fortran i/o. Our C routines will not do this,
420 chenze : so we swap explicitly here. If _BYTESWAPIO is set, this will break.
421
422 #ifdef ALLOW_ASYNCIO
423
424 IF ( filePrec.EQ.precFloat64 ) then
425
426 irec = (irecord-1)*nNz*global_nTx*ySize
427
428 call readField(MPI_COMM_MODEL, dataFName,
429 & irec,
430 & shared3dBuf_r8, tN, nNz)
431
432
433 CALL MDS_BYTESWAPR8( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r8 )
434
435 else
436 #endif
437 DO k=kLo,kHi
438 DO j=1,tNy
439 irec = 1 + ( tBx + (j-1)*iGjLoc )/sNx
440 & + ( tBy + (j-1)*jGjLoc )*global_nTx
441 & +( k-kLo + (irecord-1)*nNz )*global_nTx*ySize
442 i1 = bBij + 1 + (j-1)*sNx + (k-kLo)*sNx*sNy
443 i2 = bBij + j*sNx + (k-kLo)*sNx*sNy
444 IF ( filePrec.EQ.precFloat32 ) THEN
445 READ(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
446 ELSE
447 READ(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
448 ENDIF
449 C End of j,k loops
450 ENDDO
451 ENDDO
452
453 #ifdef ALLOW_ASYNCIO
454 endif
455 #endif
456
457
458
459
460 C end if fileIsOpen
461 c ENDIF
462
463 ELSE
464 C--- Case of 1 file per tile (globalFile=F):
465
466 C If we are reading from a tiled MDS file then we open each one here
467 iG=bi+(myXGlobalLo-1)/sNx
468 jG=bj+(myYGlobalLo-1)/sNy
469 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
470 & pfName(1:pIL),'.',iG,'.',jG,'.data'
471 INQUIRE( file=dataFName, exist=exst )
472 C Of course, we only open the file if the tile is "active"
473 C (This is a place-holder for the active/passive mechanism
474 IF (exst) THEN
475 IF ( debugLevel .GE. debLevB ) THEN
476 WRITE(msgBuf,'(A,A)')
477 & ' MDS_READ_FIELD: opening file: ',dataFName(1:pIL+13)
478 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
479 & SQUEEZE_RIGHT , myThid)
480 ENDIF
481 length_of_rec = MDS_RECLEN( filePrec, sNx*sNy*nNz, myThid )
482 OPEN( dUnit, file=dataFName, status='old',
483 & access='direct', recl=length_of_rec )
484 fileIsOpen=.TRUE.
485 ELSE
486 fileIsOpen=.FALSE.
487 WRITE(msgBuf,'(4A)') ' MDS_READ_FIELD: filename: ',
488 & fName(1:IL),' , ', dataFName(1:pIL+13)
489 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
490 & SQUEEZE_RIGHT , myThid)
491 CALL PRINT_ERROR( msgBuf, myThid )
492 WRITE(msgBuf,'(A)')
493 & ' MDS_READ_FIELD: Files DO not exist'
494 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
495 & SQUEEZE_RIGHT , myThid)
496 CALL PRINT_ERROR( msgBuf, myThid )
497 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
498 ENDIF
499
500 irec = irecord
501 i1 = bBij + 1
502 i2 = bBij + sNx*sNy*nNz
503 IF ( filePrec.EQ.precFloat32 ) THEN
504 READ(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
505 ELSE
506 READ(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
507 ENDIF
508
509 C here We close the tiled MDS file
510 IF ( fileIsOpen ) THEN
511 CLOSE( dUnit )
512 fileIsOpen = .FALSE.
513 ENDIF
514
515 C--- End Global File / tile-file cases
516 ENDIF
517
518 C End of bi,bj loops
519 ENDDO
520 ENDDO
521
522 C If global file was opened then close it
523 IF (fileIsOpen .AND. globalFile) THEN
524 CLOSE( dUnit )
525 fileIsOpen = .FALSE.
526 ENDIF
527
528 #ifdef _BYTESWAPIO
529 IF ( filePrec.EQ.precFloat32 ) THEN
530 CALL MDS_BYTESWAPR4( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r4 )
531 ELSE
532 CALL MDS_BYTESWAPR8( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r8 )
533 ENDIF
534 #endif
535
536 C- endif iAmDoingIO
537 ENDIF
538
539 C All threads wait for Master to finish reading into shared buffer
540 CALL BAR2( myThid )
541
542 C--- Copy from 3-D buffer to fldRL/RS (multi-threads):
543 IF ( filePrec.EQ.precFloat32 ) THEN
544 IF ( arrType.EQ.'RS' ) THEN
545 CALL MDS_PASS_R4toRS( shared3dBuf_r4, fldRS,
546 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
547 ELSEIF ( arrType.EQ.'RL' ) THEN
548 CALL MDS_PASS_R4toRL( shared3dBuf_r4, fldRL,
549 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
550 ELSE
551 WRITE(msgBuf,'(A)')
552 & ' MDS_READ_FIELD: illegal value for arrType'
553 CALL PRINT_ERROR( msgBuf, myThid )
554 CALL ALL_PROC_DIE( myThid )
555 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
556 ENDIF
557 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
558 IF ( arrType.EQ.'RS' ) THEN
559 CALL MDS_PASS_R8toRS( shared3dBuf_r8, fldRS,
560 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
561 ELSEIF ( arrType.EQ.'RL' ) THEN
562 CALL MDS_PASS_R8toRL( shared3dBuf_r8, fldRL,
563 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
564 ELSE
565 WRITE(msgBuf,'(A)')
566 & ' MDS_READ_FIELD: illegal value for arrType'
567 CALL PRINT_ERROR( msgBuf, myThid )
568 CALL ALL_PROC_DIE( myThid )
569 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
570 ENDIF
571 ELSE
572 WRITE(msgBuf,'(A)')
573 & ' MDS_READ_FIELD: illegal value for filePrec'
574 CALL PRINT_ERROR( msgBuf, myThid )
575 CALL ALL_PROC_DIE( myThid )
576 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
577 ENDIF
578
579 C Wait for all threads to finish getting data from 3-D shared buffer.
580 C This prevents the master-thread to change the buffer content before
581 C every one got his data.
582 CALL BAR2( myThid )
583
584 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
585 C if useSingleCpuIO / else / end
586 ENDIF
587
588 RETURN
589 END

  ViewVC Help
Powered by ViewVC 1.1.22