/[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.11 - (show annotations) (download)
Mon Jun 8 14:38:54 2009 UTC (15 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint61p
Changes since 1.10: +20 -5 lines
a hack for fizhi with NrPhys > 2*Nr

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

  ViewVC Help
Powered by ViewVC 1.1.22