/[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.17 - (show annotations) (download)
Tue Jun 7 22:33:35 2011 UTC (12 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint63, checkpoint65b, checkpoint65a, checkpoint62z
Changes since 1.16: +4 -8 lines
- refine debugLevel criteria when printing messages
- keep printing option when compiling ecco pkg (no #ifndef ALLOW_ECCO)

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_read_field.F,v 1.16 2010/12/23 02:41:47 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 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 "PARAMS.h"
70 #ifdef ALLOW_EXCH2
71 #include "W2_EXCH2_SIZE.h"
72 #include "W2_EXCH2_TOPOLOGY.h"
73 #include "W2_EXCH2_PARAMS.h"
74 #endif /* ALLOW_EXCH2 */
75 #include "EEBUFF_SCPU.h"
76 #ifdef ALLOW_FIZHI
77 # include "fizhi_SIZE.h"
78 #endif /* ALLOW_FIZHI */
79 #include "MDSIO_BUFF_3D.h"
80
81 C !INPUT PARAMETERS:
82 CHARACTER*(*) fName
83 INTEGER filePrec
84 LOGICAL useCurrentDir
85 CHARACTER*(2) arrType
86 INTEGER kSize, kLo, kHi
87 INTEGER irecord
88 INTEGER myThid
89 C !OUTPUT PARAMETERS:
90 _RL fldRL(*)
91 _RS fldRS(*)
92
93 C !FUNCTIONS
94 INTEGER ILNBLNK
95 INTEGER MDS_RECLEN
96 LOGICAL MASTER_CPU_IO
97 EXTERNAL ILNBLNK
98 EXTERNAL MDS_RECLEN
99 EXTERNAL MASTER_CPU_IO
100
101 C !LOCAL VARIABLES:
102 C bBij :: base shift in Buffer index for tile bi,bj
103 CHARACTER*(MAX_LEN_FNAM) dataFName,pfName
104 CHARACTER*(MAX_LEN_MBUF) msgBuf
105 LOGICAL exst
106 LOGICAL globalFile, fileIsOpen
107 LOGICAL iAmDoingIO
108 LOGICAL useExch2ioLayOut
109 INTEGER xSize, ySize
110 INTEGER iG,jG,bi,bj
111 INTEGER i1,i2,i,j,k,nNz
112 INTEGER irec,dUnit,IL,pIL
113 INTEGER length_of_rec
114 INTEGER bBij
115 INTEGER tNx, tNy, global_nTx
116 INTEGER tBx, tBy, iGjLoc, jGjLoc
117 #ifdef ALLOW_EXCH2
118 INTEGER tN
119 #endif /* ALLOW_EXCH2 */
120
121 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122 C Set dimensions:
123 xSize = Nx
124 ySize = Ny
125 useExch2ioLayOut = .FALSE.
126 #ifdef ALLOW_EXCH2
127 IF ( W2_useE2ioLayOut ) THEN
128 xSize = exch2_global_Nx
129 ySize = exch2_global_Ny
130 useExch2ioLayOut = .TRUE.
131 ENDIF
132 #endif /* ALLOW_EXCH2 */
133
134 C Assume nothing
135 globalFile = .FALSE.
136 fileIsOpen = .FALSE.
137 IL = ILNBLNK( fName )
138 pIL = ILNBLNK( mdsioLocalDir )
139 nNz = 1 + kHi - kLo
140
141 C Only do I/O if I am the master thread (and mpi process 0 IF useSingleCpuIO):
142 iAmDoingIO = MASTER_CPU_IO(myThid)
143
144 C Record number must be >= 1
145 IF (irecord .LT. 1) THEN
146 WRITE(msgBuf,'(3A,I10)')
147 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
148 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
149 & SQUEEZE_RIGHT , myThid )
150 WRITE(msgBuf,'(A,I9.8)')
151 & ' MDS_READ_FIELD: argument irecord = ',irecord
152 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
153 & SQUEEZE_RIGHT , myThid )
154 WRITE(msgBuf,'(A)')
155 & ' MDS_READ_FIELD: Invalid value for irecord'
156 CALL PRINT_ERROR( msgBuf, myThid )
157 CALL ALL_PROC_DIE( myThid )
158 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
159 ENDIF
160 C check for valid sub-set of levels:
161 IF ( kLo.LT.1 .OR. kHi.GT.kSize ) THEN
162 WRITE(msgBuf,'(3A,I10)')
163 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
164 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
165 & SQUEEZE_RIGHT , myThid )
166 WRITE(msgBuf,'(3(A,I6))')
167 & ' MDS_READ_FIELD: arguments kSize=', kSize,
168 & ' , kLo=', kLo, ' , kHi=', kHi
169 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
170 & SQUEEZE_RIGHT , myThid )
171 WRITE(msgBuf,'(A)')
172 & ' MDS_READ_FIELD: invalid sub-set of levels'
173 CALL PRINT_ERROR( msgBuf, myThid )
174 CALL ALL_PROC_DIE( myThid )
175 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
176 ENDIF
177 C check for 3-D Buffer size:
178 IF ( .NOT.useSingleCpuIO .AND. nNz.GT.size3dBuf ) THEN
179 WRITE(msgBuf,'(3A,I10)')
180 & ' MDS_READ_FIELD: file="', fName(1:IL), '"'
181 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
182 & SQUEEZE_RIGHT , myThid )
183 WRITE(msgBuf,'(3(A,I6))')
184 & ' MDS_READ_FIELD: Nb Lev to read =', nNz,
185 & ' >', size3dBuf, ' = buffer 3rd Dim'
186 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
187 & SQUEEZE_RIGHT , myThid )
188 WRITE(msgBuf,'(A)')
189 & ' MDS_READ_FIELD: buffer 3rd Dim. too small'
190 CALL PRINT_ERROR( msgBuf, myThid )
191 WRITE(msgBuf,'(A)')
192 & ' increase "size3dBuf" in "MDSIO_BUFF_3D.h" and recompile'
193 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
194 & SQUEEZE_RIGHT , myThid )
195 CALL ALL_PROC_DIE( myThid )
196 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
197 ENDIF
198
199 C Only do I/O if I am the master thread
200 IF ( iAmDoingIO ) THEN
201
202 C Assign special directory
203 IF ( useCurrentDir .OR. pIL.EQ.0 ) THEN
204 pfName= fName
205 ELSE
206 WRITE(pfName,'(2a)') mdsioLocalDir(1:pIL), fName(1:IL)
207 ENDIF
208 pIL=ILNBLNK( pfName )
209
210 C Assign a free unit number as the I/O channel for this routine
211 CALL MDSFINDUNIT( dUnit, myThid )
212
213 C Check first for global file with simple name (ie. fName)
214 dataFName = fName
215 INQUIRE( file=dataFName, exist=exst )
216 IF (exst) THEN
217 IF ( debugLevel .GE. debLevB ) THEN
218 WRITE(msgBuf,'(A,A)')
219 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL)
220 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
221 & SQUEEZE_RIGHT , myThid)
222 ENDIF
223 globalFile = .TRUE.
224 ENDIF
225
226 C If negative check for global file with MDS name (ie. fName.data)
227 IF (.NOT. globalFile) THEN
228 WRITE(dataFName,'(2a)') fName(1:IL),'.data'
229 INQUIRE( file=dataFName, exist=exst )
230 IF (exst) THEN
231 IF ( debugLevel .GE. debLevB ) THEN
232 WRITE(msgBuf,'(A,A)')
233 & ' MDS_READ_FIELD: opening global file: ',dataFName(1:IL+5)
234 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
235 & SQUEEZE_RIGHT , myThid)
236 ENDIF
237 globalFile = .TRUE.
238 ENDIF
239 ENDIF
240
241 C- endif iAmDoingIO
242 ENDIF
243
244 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
245
246 IF ( useSingleCPUIO ) THEN
247
248 C master thread of process 0, only, opens a global file
249 IF ( iAmDoingIO ) THEN
250 C If global file is visible to process 0, then open it here.
251 C Otherwise stop program.
252 IF ( globalFile) THEN
253 length_of_rec = MDS_RECLEN( filePrec, xSize*ySize, myThid )
254 OPEN( dUnit, file=dataFName, status='old',
255 & access='direct', recl=length_of_rec )
256 ELSE
257 WRITE(msgBuf,'(2A)')
258 & ' MDS_READ_FIELD: filename: ', dataFName(1:IL+5)
259 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
260 & SQUEEZE_RIGHT , myThid)
261 CALL PRINT_ERROR( msgBuf, myThid )
262 WRITE(msgBuf,'(A)')
263 & ' MDS_READ_FIELD: File does not exist'
264 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
265 & SQUEEZE_RIGHT , myThid)
266 CALL PRINT_ERROR( msgBuf, myThid )
267 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
268 ENDIF
269 C- endif iAmDoingIO
270 ENDIF
271
272 DO k=kLo,kHi
273
274 C master thread of process 0, only, read from file
275 IF ( iAmDoingIO ) THEN
276 irec = 1 + k-kLo + (irecord-1)*nNz
277 IF (filePrec .EQ. precFloat32) THEN
278 READ(dUnit,rec=irec) ( xy_buffer_r4(i),i=1,xSize*ySize )
279 #ifdef _BYTESWAPIO
280 CALL MDS_BYTESWAPR4( xSize*ySize, xy_buffer_r4 )
281 #endif
282 ELSE
283 READ(dUnit,rec=irec) ( xy_buffer_r8(i),i=1,xSize*ySize )
284 #ifdef _BYTESWAPIO
285 CALL MDS_BYTESWAPR8( xSize*ySize, xy_buffer_r8 )
286 #endif
287 ENDIF
288 C- endif iAmDoingIO
289 ENDIF
290
291 C Wait for all thread to finish. This prevents other threads to continue
292 C to acces shared buffer while master thread is loading data into
293 CALL BAR2( myThid )
294
295 IF ( filePrec.EQ.precFloat32 ) THEN
296 CALL SCATTER_2D_R4(
297 U xy_buffer_r4,
298 O sharedLocBuf_r4,
299 I xSize, ySize,
300 I useExch2ioLayOut, .FALSE., myThid )
301 C All threads wait for Master to finish loading into shared buffer
302 CALL BAR2( myThid )
303 IF ( arrType.EQ.'RS' ) THEN
304 CALL MDS_PASS_R4toRS( sharedLocBuf_r4, fldRS,
305 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
306 ELSEIF ( arrType.EQ.'RL' ) THEN
307 CALL MDS_PASS_R4toRL( sharedLocBuf_r4, fldRL,
308 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
309 ELSE
310 WRITE(msgBuf,'(A)')
311 & ' MDS_READ_FIELD: illegal value for arrType'
312 CALL PRINT_ERROR( msgBuf, myThid )
313 CALL ALL_PROC_DIE( myThid )
314 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
315 ENDIF
316 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
317 CALL SCATTER_2D_R8(
318 U xy_buffer_r8,
319 O sharedLocBuf_r8,
320 I xSize, ySize,
321 I useExch2ioLayOut, .FALSE., myThid )
322 C All threads wait for Master to finish loading into shared buffer
323 CALL BAR2( myThid )
324 IF ( arrType.EQ.'RS' ) THEN
325 CALL MDS_PASS_R8toRS( sharedLocBuf_r8, fldRS,
326 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
327 ELSEIF ( arrType.EQ.'RL' ) THEN
328 CALL MDS_PASS_R8toRL( sharedLocBuf_r8, fldRL,
329 I 0, 0, 1, k, kSize, 0, 0, .TRUE., myThid )
330 ELSE
331 WRITE(msgBuf,'(A)')
332 & ' MDS_READ_FIELD: illegal value for arrType'
333 CALL PRINT_ERROR( msgBuf, myThid )
334 CALL ALL_PROC_DIE( myThid )
335 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
336 ENDIF
337 ELSE
338 WRITE(msgBuf,'(A)')
339 & ' MDS_READ_FIELD: illegal value for filePrec'
340 CALL PRINT_ERROR( msgBuf, myThid )
341 CALL ALL_PROC_DIE( myThid )
342 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
343 ENDIF
344
345 ENDDO
346 c ENDDO k=kLo,kHi
347
348 IF ( iAmDoingIO ) THEN
349 CLOSE( dUnit )
350 ENDIF
351
352 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
353 C--- else .NOT.useSingleCpuIO
354 ELSE
355
356 C Wait for all thread to finish. This prevents other threads to continue
357 C to acces 3-D buffer while master thread is reading
358 c CALL BAR2( myThid )
359
360 C Only do I/O if I am the master thread
361 IF ( iAmDoingIO ) THEN
362
363 C If we are reading from a global file then we open it here
364 IF (globalFile) THEN
365 length_of_rec = MDS_RECLEN( filePrec, sNx, myThid )
366 OPEN( dUnit, file=dataFName, status='old',
367 & access='direct', recl=length_of_rec )
368 fileIsOpen=.TRUE.
369 ENDIF
370
371 C Loop over all tiles
372 DO bj=1,nSy
373 DO bi=1,nSx
374 bBij = sNx*sNy*nNz*( bi-1 + (bj-1)*nSx )
375
376 IF (globalFile) THEN
377 C--- Case of 1 Global file:
378
379 c IF (fileIsOpen) THEN
380 tNx = sNx
381 tNy = sNy
382 global_nTx = xSize/sNx
383 tBx = myXGlobalLo-1 + (bi-1)*sNx
384 tBy = myYGlobalLo-1 + (bj-1)*sNy
385 iGjLoc = 0
386 jGjLoc = 1
387 #ifdef ALLOW_EXCH2
388 IF ( useExch2ioLayOut ) THEN
389 tN = W2_myTileList(bi,bj)
390 c tNx = exch2_tNx(tN)
391 c tNy = exch2_tNy(tN)
392 c global_nTx = exch2_global_Nx/tNx
393 tBx = exch2_txGlobalo(tN) - 1
394 tBy = exch2_tyGlobalo(tN) - 1
395 IF ( exch2_mydNx(tN) .GT. xSize ) THEN
396 C- face x-size larger than glob-size : fold it
397 iGjLoc = 0
398 jGjLoc = exch2_mydNx(tN) / xSize
399 ELSEIF ( exch2_tNy(tN) .GT. ySize ) THEN
400 C- tile y-size larger than glob-size : make a long line
401 iGjLoc = exch2_mydNx(tN)
402 jGjLoc = 0
403 ELSE
404 C- default (face fit into global-IO-array)
405 iGjLoc = 0
406 jGjLoc = 1
407 ENDIF
408 ENDIF
409 #endif /* ALLOW_EXCH2 */
410
411 DO k=kLo,kHi
412 DO j=1,tNy
413 irec = 1 + ( tBx + (j-1)*iGjLoc )/sNx
414 & + ( tBy + (j-1)*jGjLoc )*global_nTx
415 & +( k-kLo + (irecord-1)*nNz )*global_nTx*ySize
416 i1 = bBij + 1 + (j-1)*sNx + (k-kLo)*sNx*sNy
417 i2 = bBij + j*sNx + (k-kLo)*sNx*sNy
418 IF ( filePrec.EQ.precFloat32 ) THEN
419 READ(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
420 ELSE
421 READ(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
422 ENDIF
423 C End of j,k loops
424 ENDDO
425 ENDDO
426
427 C end if fileIsOpen
428 c ENDIF
429
430 ELSE
431 C--- Case of 1 file per tile (globalFile=F):
432
433 C If we are reading from a tiled MDS file then we open each one here
434 iG=bi+(myXGlobalLo-1)/sNx
435 jG=bj+(myYGlobalLo-1)/sNy
436 WRITE(dataFName,'(2A,I3.3,A,I3.3,A)')
437 & pfName(1:pIL),'.',iG,'.',jG,'.data'
438 INQUIRE( file=dataFName, exist=exst )
439 C Of course, we only open the file if the tile is "active"
440 C (This is a place-holder for the active/passive mechanism
441 IF (exst) THEN
442 IF ( debugLevel .GE. debLevB ) THEN
443 WRITE(msgBuf,'(A,A)')
444 & ' MDS_READ_FIELD: opening file: ',dataFName(1:pIL+13)
445 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
446 & SQUEEZE_RIGHT , myThid)
447 ENDIF
448 length_of_rec = MDS_RECLEN( filePrec, sNx*sNy*nNz, myThid )
449 OPEN( dUnit, file=dataFName, status='old',
450 & access='direct', recl=length_of_rec )
451 fileIsOpen=.TRUE.
452 ELSE
453 fileIsOpen=.FALSE.
454 WRITE(msgBuf,'(4A)') ' MDS_READ_FIELD: filename: ',
455 & fName(1:IL),' , ', dataFName(1:pIL+13)
456 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
457 & SQUEEZE_RIGHT , myThid)
458 CALL PRINT_ERROR( msgBuf, myThid )
459 WRITE(msgBuf,'(A)')
460 & ' MDS_READ_FIELD: Files DO not exist'
461 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
462 & SQUEEZE_RIGHT , myThid)
463 CALL PRINT_ERROR( msgBuf, myThid )
464 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
465 ENDIF
466
467 irec = irecord
468 i1 = bBij + 1
469 i2 = bBij + sNx*sNy*nNz
470 IF ( filePrec.EQ.precFloat32 ) THEN
471 READ(dUnit,rec=irec) (shared3dBuf_r4(i),i=i1,i2)
472 ELSE
473 READ(dUnit,rec=irec) (shared3dBuf_r8(i),i=i1,i2)
474 ENDIF
475
476 C here We close the tiled MDS file
477 IF ( fileIsOpen ) THEN
478 CLOSE( dUnit )
479 fileIsOpen = .FALSE.
480 ENDIF
481
482 C--- End Global File / tile-file cases
483 ENDIF
484
485 C End of bi,bj loops
486 ENDDO
487 ENDDO
488
489 C If global file was opened then close it
490 IF (fileIsOpen .AND. globalFile) THEN
491 CLOSE( dUnit )
492 fileIsOpen = .FALSE.
493 ENDIF
494
495 #ifdef _BYTESWAPIO
496 IF ( filePrec.EQ.precFloat32 ) THEN
497 CALL MDS_BYTESWAPR4( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r4 )
498 ELSE
499 CALL MDS_BYTESWAPR8( sNx*sNy*nNz*nSx*nSy, shared3dBuf_r8 )
500 ENDIF
501 #endif
502
503 C- endif iAmDoingIO
504 ENDIF
505
506 C All threads wait for Master to finish reading into shared buffer
507 CALL BAR2( myThid )
508
509 C--- Copy from 3-D buffer to fldRL/RS (multi-threads):
510 IF ( filePrec.EQ.precFloat32 ) THEN
511 IF ( arrType.EQ.'RS' ) THEN
512 CALL MDS_PASS_R4toRS( shared3dBuf_r4, fldRS,
513 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
514 ELSEIF ( arrType.EQ.'RL' ) THEN
515 CALL MDS_PASS_R4toRL( shared3dBuf_r4, fldRL,
516 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
517 ELSE
518 WRITE(msgBuf,'(A)')
519 & ' MDS_READ_FIELD: illegal value for arrType'
520 CALL PRINT_ERROR( msgBuf, myThid )
521 CALL ALL_PROC_DIE( myThid )
522 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
523 ENDIF
524 ELSEIF ( filePrec.EQ.precFloat64 ) THEN
525 IF ( arrType.EQ.'RS' ) THEN
526 CALL MDS_PASS_R8toRS( shared3dBuf_r8, fldRS,
527 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
528 ELSEIF ( arrType.EQ.'RL' ) THEN
529 CALL MDS_PASS_R8toRL( shared3dBuf_r8, fldRL,
530 I 0, 0, nNz, kLo, kSize, 0, 0, .TRUE., myThid )
531 ELSE
532 WRITE(msgBuf,'(A)')
533 & ' MDS_READ_FIELD: illegal value for arrType'
534 CALL PRINT_ERROR( msgBuf, myThid )
535 CALL ALL_PROC_DIE( myThid )
536 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
537 ENDIF
538 ELSE
539 WRITE(msgBuf,'(A)')
540 & ' MDS_READ_FIELD: illegal value for filePrec'
541 CALL PRINT_ERROR( msgBuf, myThid )
542 CALL ALL_PROC_DIE( myThid )
543 STOP 'ABNORMAL END: S/R MDS_READ_FIELD'
544 ENDIF
545
546 C Wait for all threads to finish getting data from 3-D shared buffer.
547 C This prevents the master-thread to change the buffer content before
548 C every one got his data.
549 CALL BAR2( myThid )
550
551 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
552 C if useSingleCpuIO / else / end
553 ENDIF
554
555 RETURN
556 END

  ViewVC Help
Powered by ViewVC 1.1.22