/[MITgcm]/MITgcm/pkg/rw/read_mflds.F
ViewVC logotype

Contents of /MITgcm/pkg/rw/read_mflds.F

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


Revision 1.3 - (show annotations) (download)
Tue Nov 13 19:41:05 2007 UTC (16 years, 6 months ago) by jmc
Branch: MAIN
Changes since 1.2: +9 -4 lines
cleaning-up: call directly new MDSIO S/R MDS_READ/WRITE_FIELD

1 C $Header: /u/gcmpack/MITgcm/pkg/rw/read_mflds.F,v 1.2 2007/10/23 15:17:24 jmc Exp $
2 C $Name: $
3
4 #include "RW_OPTIONS.h"
5
6 C-- File read_mflds.F: Routines to handle reading Multi-Fields File (+ meta file)
7 C-- Contents
8 C-- o READ_MFLDS_INIT
9 C-- o READ_MFLDS_SET
10 C-- o READ_MFLDS_3D_RL
11 C-- o READ_MFLDS_CHECK
12
13 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
14 CBOP
15 C !ROUTINE: READ_MFLDS_INIT
16 C !INTERFACE:
17 SUBROUTINE READ_MFLDS_INIT(
18 I myThid )
19
20 C !DESCRIPTION:
21 C Initialise Multi-Fields read variables in common block
22
23 C !USES:
24 IMPLICIT NONE
25 c#include "SIZE.h"
26 #include "EEPARAMS.h"
27 #include "RW_MFLDS.h"
28
29 C !INPUT/OUTPUT PARAMETERS:
30 C myThid :: my Thread Id. number
31 INTEGER myThid
32 CEOP
33
34 C !LOCAL VARIABLES:
35 C i :: loop counter
36 INTEGER i
37 C- for debug print:
38 c CHARACTER*(MAX_LEN_MBUF) msgBuf
39
40 C-----
41
42 C- Initialise variables in common block:
43 thirdDim = 0
44 nFl3D = 0
45 nFlds = 0
46 nMissFld = 0
47 mFldsFile = ' '
48 DO i=1,sizFldList
49 fldList(i) = ' '
50 fldMiss(i) = ' '
51 ENDDO
52
53 RETURN
54 END
55
56 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
57 CBOP
58 C !ROUTINE: READ_MFLDS_SET
59 C !INTERFACE:
60 SUBROUTINE READ_MFLDS_SET(
61 I fName,
62 O nbFields, filePrec,
63 I fileDim3, myIter, myThid )
64
65 C !DESCRIPTION:
66 C This is the controlling routine for preparing Multi-Fields read
67 C by reading the corresponding meta file.
68 C the meta-file content is stored in common block (header: RW_MFLDS.h)
69 C to be reachable by all threads
70
71 C Note: 1) Output arguments should not be shared variables (= not in common block)
72 C 2) Only master-thread returns a valid filePrec (others just return 0)
73
74 C !USES:
75 IMPLICIT NONE
76 #include "SIZE.h"
77 #include "EEPARAMS.h"
78 #include "PARAMS.h"
79 #include "RW_MFLDS.h"
80
81 C !INPUT/OUTPUT PARAMETERS:
82 C fName :: current MFLDS file name (prefix) to read
83 C nbFields :: Number of fields in current MFLDS file
84 C filePrec :: data-precision in current MFLDS file
85 C fileDim3 :: 3rd dimension of fields in current MFLDS file
86 C myIter :: Iteration number
87 C myThid :: my Thread Id. number
88 CHARACTER*(MAX_LEN_FNAM) fName
89 INTEGER nbFields
90 INTEGER filePrec
91 INTEGER fileDim3
92 INTEGER myIter
93 INTEGER myThid
94 CEOP
95
96 C !FUNCTIONS
97 INTEGER ILNBLNK
98 EXTERNAL ILNBLNK
99
100 C !LOCAL VARIABLES:
101 C- do change dir. (using mdsioLocalDir):
102 LOGICAL useCurrentDir
103 C- output of MDS_READ_META :
104 INTEGER nSizD, nSizT
105 PARAMETER( nSizD = 5 , nSizT = 20 )
106 CHARACTER*(MAX_LEN_PREC/2) simulName
107 CHARACTER*(MAX_LEN_MBUF/2) titleLine
108 INTEGER nDims, nTimRec
109 INTEGER dimList(3,nSizD)
110 _RL timList(nSizT)
111 INTEGER nRecords, fileIter
112 C- for debug print:
113 INTEGER i, j, ioUnit
114 CHARACTER*(MAX_LEN_MBUF) msgBuf
115
116 C-----
117
118 C- Initialise output arguments:
119 nbFields = 0
120 filePrec = 0
121
122 #ifdef RW_SAFE_MFLDS
123 i = ILNBLNK(mFldsFile)
124 IF ( i.NE.0 ) THEN
125 i = MIN(i, MAX_LEN_MBUF-48-34 )
126 WRITE(msgBuf,'(4A)') 'READ_MFLDS_SET: ',
127 & 'MFLDS file-name already set to: ',mFldsFile(1:i)
128 CALL PRINT_ERROR( msgBuf, myThid )
129 STOP 'ABNORMAL END: S/R READ_MFLDS_SET (fileName)'
130 ENDIF
131 _BARRIER
132 #endif /* RW_SAFE_MFLDS */
133 _BEGIN_MASTER( myThid )
134
135 C- Initialise variables in common block:
136 thirdDim = fileDim3
137 nFl3D = 0
138 nFlds = 0
139 nMissFld = 0
140 mFldsFile = fName
141 DO i=1,sizFldList
142 fldList(i) = ' '
143 fldMiss(i) = ' '
144 ENDDO
145
146 #ifdef ALLOW_MDSIO
147 useCurrentDir = .FALSE.
148 nDims = nSizD
149 nFlds = sizFldList
150 nTimRec = nSizT
151 CALL MDS_READ_META(
152 I fName,
153 O simulName,
154 O titleLine,
155 O filePrec,
156 U nDims, nFlds, nTimRec,
157 O dimList, fldList, timList,
158 O nRecords, fileIter,
159 I useCurrentDir, myThid )
160 #endif /* ALLOW_MDSIO */
161
162 C- evaluate Nb of 3.D fields (used if mix 3-D & 2-D fields in file):
163 nFl3D = 0
164 IF ( nFlds.GE.1 ) THEN
165 IF ( nDims.EQ.2 .AND. thirdDim.GT.1
166 & .AND. nFlds.LT.nRecords ) THEN
167 IF ( MOD( nRecords-nFlds , thirdDim-1 ) .EQ. 0 )
168 & nFl3D = (nRecords-nFlds)/(thirdDim-1)
169 ENDIF
170 IF ( nFlds.NE.nRecords .AND. nFl3D.EQ.0 ) THEN
171 C- here we have a problem
172 WRITE(msgBuf,'(A,I5,A,I4,A)')
173 & 'READ_MFLDS_SET: Pb with Nb of records=', nRecords,
174 & ' (3rd-Dim=', thirdDim,')'
175 CALL PRINT_ERROR( msgBuf, myThid )
176 WRITE(msgBuf,'(A,I5,A,I4,A)')
177 & ' does not match Nb of flds=', nFlds
178 CALL PRINT_ERROR( msgBuf, myThid )
179 STOP 'ABNORMAL END: S/R READ_MFLDS_SET (Nb-records Pb)'
180 ENDIF
181 c IF ( nFl3D.EQ.0 ) nFl3D = nFlds
182 ENDIF
183
184 C- write to Standard Output
185 IF ( debugLevel.GE.debLevA ) THEN
186 ioUnit = standardMessageUnit
187 i = ILNBLNK(simulName)
188 IF ( i.GE.1 ) THEN
189 WRITE(msgBuf,'(3A)') ' simulName=>', simulName(1:i), '<'
190 CALL PRINT_MESSAGE(msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
191 ENDIF
192 i = ILNBLNK(titleLine)
193 IF ( i.GE.1 ) THEN
194 WRITE(msgBuf,'(3A)') ' titleLine=>', titleLine(1:i), '<'
195 CALL PRINT_MESSAGE(msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
196 ENDIF
197 WRITE(msgBuf,'(2(A,I4),A,I10)')
198 & ' nRecords =', nRecords, ' ; filePrec =', filePrec,
199 & ' ; fileIter =', fileIter
200 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
201 WRITE(msgBuf,'(A,I4,A)') ' nDims =', nDims, ' , dims:'
202 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
203 DO j=1,nDims
204 WRITE(msgBuf,'(I4,A,3I4)') j,':',(dimList(i,j),i=1,3)
205 CALL PRINT_MESSAGE(msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
206 ENDDO
207 WRITE(msgBuf,'(3(A,I4))')
208 & ' nFlds =', nFlds, ' , nFl3D =', nFl3D, ' , fields:'
209 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
210 DO j=1,nFlds,20
211 WRITE(msgBuf,'(20(A2,A8,A))')
212 & (' >', fldList(i), '<', i=j,MIN(j+19,nFlds) )
213 CALL PRINT_MESSAGE(msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
214 ENDDO
215 WRITE(msgBuf,'(A,I4,A)') ' nTimRec =',nTimRec,' , timeList:'
216 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
217 IF ( nTimRec.GE.1 ) THEN
218 WRITE(msgBuf,'(1P20E20.12)') (timList(i),i=1,nTimRec)
219 CALL PRINT_MESSAGE(msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
220 ENDIF
221 ENDIF
222
223 _END_MASTER( myThid )
224 _BARRIER
225
226 C- set output arguments:
227 nbFields = nFlds
228
229 RETURN
230 END
231
232 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
233 CBOP
234 C !ROUTINE: READ_MFLDS_3D_RL
235 C !INTERFACE:
236 SUBROUTINE READ_MFLDS_3D_RL(
237 I fldName,
238 O field,
239 U nj,
240 I fPrec, nNz, myIter, myThid )
241
242 C !DESCRIPTION:
243 C Read, from a Multi-Fields binary file, field "fldName" into array "field"
244 C record Nb "nj" is search through the field-list (from meta-file) which
245 C has been set before (calling READ_MFLDS_SET).
246 C In case nFlds is <=0 , by-pass the search and directly read record number "nj"
247
248 C !USES:
249 IMPLICIT NONE
250 #include "SIZE.h"
251 #include "EEPARAMS.h"
252 #include "PARAMS.h"
253 #include "RW_MFLDS.h"
254
255 C !INPUT/OUTPUT PARAMETERS:
256 C fldName :: Name of the field to read
257 C field :: Output array to read in
258 C nj (in) :: number of the record (in file) just before the one to read
259 C nj (out):: number of the record (from current file) which was read in
260 C fPrec :: File precision (number of bits per word, = 32 or 64)
261 C nNz :: Number of levels to read in
262 C myIter :: Iteration number
263 C myThid :: My Thread Id number
264 CHARACTER*(8) fldName
265 _RL field(*)
266 INTEGER nj
267 INTEGER fPrec
268 INTEGER nNz
269 INTEGER myIter
270 INTEGER myThid
271 CEOP
272
273 C !FUNCTIONS
274 INTEGER ILNBLNK
275 EXTERNAL ILNBLNK
276
277 C !LOCAL VARIABLES:
278 INTEGER j, iL, ioUnit
279 LOGICAL useCurrentDir
280 CHARACTER*(2) fType
281 CHARACTER*(MAX_LEN_FNAM) fName
282 CHARACTER*(MAX_LEN_MBUF) msgBuf
283
284 C-----
285
286 iL = ILNBLNK(mFldsFile)
287 #ifdef RW_SAFE_MFLDS
288 IF ( iL.EQ.0 ) THEN
289 WRITE(msgBuf,'(2A,I4)') 'READ_MFLDS_3D_RL: ',
290 & 'empty MFLDS file-name'
291 CALL PRINT_ERROR( msgBuf, myThid )
292 STOP 'ABNORMAL END: S/R READ_MFLDS_3D_RL (fileName)'
293 ENDIF
294 #endif /* RW_SAFE_MFLDS */
295
296 ioUnit = standardMessageUnit
297 IF ( nFlds.GE.1 ) THEN
298 C-- Search for "fldName" in list of field-names:
299 nj = 0
300 DO j=1,nFlds
301 IF ( fldName.EQ.fldList(j) .AND. nj.EQ.0 ) nj = j
302 ENDDO
303 IF ( nj.EQ.0 ) THEN
304 C- record unsuccessful search:
305 _BEGIN_MASTER( myThid )
306 nMissFld = nMissFld + 1
307 j = MIN(nMissFld,sizFldList)
308 fldMiss(j) = fldName
309 _END_MASTER( myThid )
310 IF ( debugLevel.GE.debLevA ) THEN
311 iL = ILNBLNK(mFldsFile)
312 iL = MIN(iL,MAX_LEN_MBUF-54-20)
313 WRITE(msgBuf,'(5A)') 'READ_MFLDS_3D_RL: ',
314 & 'field: "',fldName,'" missing in file: ',mFldsFile(1:iL)
315 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
316 ENDIF
317 ELSE
318 C- convert from field Number to record number (if mix of 3D & 2D flds)
319 j = nj
320 IF ( nj.GT.nFl3D ) nj = nj + nFl3D*(thirdDim-1)
321 IF ( debugLevel.GE.debLevA ) THEN
322 WRITE(msgBuf,'(3A,2(A,I4))') 'READ_MFLDS_3D_RL: ',
323 & 'read field: "',fldName,'", #',j,' in fldList, rec=',nj
324 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
325 ENDIF
326 ENDIF
327 ELSEIF ( nj.GE.0 ) THEN
328 C- increment record number
329 nj = nj + 1
330 IF ( debugLevel.GE.debLevA ) THEN
331 WRITE(msgBuf,'(3A,2(A,I4))') 'READ_MFLDS_3D_RL: ',
332 & 'no fldList, try to read field "',fldName, '", rec=',nj
333 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
334 ENDIF
335 ENDIF
336
337 IF ( nj.GE.1 ) THEN
338 C-- read in array "field"
339 fName = mFldsFile
340 useCurrentDir = .FALSE.
341 fType = 'RL'
342 #ifdef ALLOW_MDSIO
343 CALL MDS_READ_FIELD(
344 I fName, fPrec, useCurrentDir,
345 I fType, nNz, 1, nNz,
346 O field,
347 I nj, myThid )
348
349 #endif
350 ENDIF
351
352 RETURN
353 END
354
355 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
356 CBOP
357 C !ROUTINE: READ_MFLDS_CHECK
358 C !INTERFACE:
359 SUBROUTINE READ_MFLDS_CHECK(
360 O errList,
361 U nbErr,
362 I myIter, myThid )
363
364 C !DESCRIPTION:
365 C After reading a Multi-Fields binary file, check (and report)
366 C for missing fields (attempted to read but not found).
367 C
368 C Note: If missing fields, print error msg but take no action (no stop)
369 C but return number of missing fields (+ list, if nbErr_inputArg > 0)
370 C Depending on the calling context, may choose to stop or to continue
371
372 C !USES:
373 IMPLICIT NONE
374 #include "SIZE.h"
375 #include "EEPARAMS.h"
376 #include "PARAMS.h"
377 #include "RW_MFLDS.h"
378
379 C !INPUT PARAMETERS:
380 C nbErr :: max size of array errList
381 C myIter :: Iteration number
382 C myThid :: My Thread Id number
383 C !OUTPUT PARAMETERS:
384 C errList :: List of missing fields (attempted to read but not found)
385 C nbErr :: Number of missing fields (attempted to read but not found)
386 CHARACTER*(8) errList(*)
387 INTEGER nbErr
388 INTEGER myIter
389 INTEGER myThid
390 CEOP
391
392 C !FUNCTIONS
393 INTEGER ILNBLNK
394 EXTERNAL ILNBLNK
395
396 C !LOCAL VARIABLES:
397 INTEGER i, j, nj, iL, ioUnit
398 CHARACTER*(MAX_LEN_MBUF) msgBuf
399
400 C-----
401
402 iL = ILNBLNK(mFldsFile)
403 #ifdef RW_SAFE_MFLDS
404 IF ( iL.EQ.0 ) THEN
405 WRITE(msgBuf,'(2A,I4)') 'READ_MFLDS_CHECK: ',
406 & 'empty MFLDS file-name'
407 CALL PRINT_ERROR( msgBuf, myThid )
408 STOP 'ABNORMAL END: S/R READ_MFLDS_CHECK (fileName)'
409 ENDIF
410 #endif /* RW_SAFE_MFLDS */
411
412 C-- Initialise output arguments
413 DO j=1,nbErr
414 errList(j) = ' '
415 ENDDO
416
417 IF ( nMissFld.GE.1 ) THEN
418 C-- Attempted to read some fields that were not in the current MFLDS file
419 C => report by printing Error Msg:
420 ioUnit = errorMessageUnit
421 WRITE(msgBuf,'(3A)') 'READ_MFLDS_CHECK: ',
422 & 'reading from file: ', mFldsFile(1:iL)
423 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
424 WRITE(msgBuf,'(2A,I4,A)') 'READ_MFLDS_CHECK: ',
425 & 'which contains ', nFlds, ' fields :'
426 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
427 DO j=1,nFlds,20
428 WRITE(msgBuf,'(20(A2,A8,A))')
429 & (' >', fldList(i), '<', i=j,MIN(j+19,nFlds) )
430 CALL PRINT_MESSAGE(msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
431 ENDDO
432 WRITE(msgBuf,'(A,I4,A)') 'READ_MFLDS_CHECK: ',
433 & nMissFld, ' field(s) is/are missing :'
434 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
435 nj = MIN( nMissFld, sizFldList )
436 DO j=1,nj,20
437 WRITE(msgBuf,'(20(A2,A8,A))')
438 & (' >', fldMiss(i), '<', i=j,MIN(j+19,nj) )
439 CALL PRINT_MESSAGE(msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
440 ENDDO
441
442 C- Size problem:
443 IF ( nMissFld.GT.sizFldList ) THEN
444 WRITE(msgBuf,'(2A,I4)') 'READ_MFLDS_CHECK: ',
445 & 'missing fields list has been truncated to', sizFldList
446 CALL PRINT_ERROR( msgBuf, myThid )
447 STOP 'ABNORMAL END: S/R READ_MFLDS_CHECK (list-size Pb)'
448 ENDIF
449
450 C- Fill the error output list (up to the Max size: nbErr)
451 nj = MIN( nMissFld, nbErr )
452 DO j=1,nj
453 errList(j) = fldMiss(j)
454 ENDDO
455 ELSE
456 C-- Normal end : print msg before resetting "mFldsFile"
457 ioUnit = standardMessageUnit
458 IF ( debugLevel .GE. debLevA ) THEN
459 WRITE(msgBuf,'(3A)') 'READ_MFLDS_CHECK: ',
460 c & '- end reading file: ', mFldsFile(1:iL)
461 c & '- normal end ; reset mFldsFile: ', mFldsFile(1:iL)
462 & '- normal end ; reset MFLDS file-name: ', mFldsFile(1:iL)
463 CALL PRINT_MESSAGE( msgBuf, ioUnit, SQUEEZE_RIGHT, myThid )
464 ENDIF
465
466 ENDIF
467
468 C- Return the number of missing fields
469 nbErr = nMissFld
470
471 #ifdef RW_SAFE_MFLDS
472 _BARRIER
473 _BEGIN_MASTER( myThid )
474 C-- Reset MFLDS file name:
475 mFldsFile = ' '
476 _END_MASTER( myThid )
477 _BARRIER
478 #endif /* RW_SAFE_MFLDS */
479
480 RETURN
481 END

  ViewVC Help
Powered by ViewVC 1.1.22