/[MITgcm]/MITgcm/pkg/mdsio/mdsio_read_meta.F
ViewVC logotype

Contents of /MITgcm/pkg/mdsio/mdsio_read_meta.F

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


Revision 1.7 - (show annotations) (download)
Sun Jan 13 22:48:49 2013 UTC (11 years, 3 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, checkpoint64c, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, HEAD
Changes since 1.6: +20 -9 lines
- read timeInterval (consistent with revision 1.5 of mdsio_write_meta.F)
  instead of "modelTime" ;
- read missingValue (if present)

1 C $Header: /u/gcmpack/MITgcm/pkg/mdsio/mdsio_read_meta.F,v 1.6 2012/07/16 19:14:49 jmc Exp $
2 C $Name: $
3
4 #include "MDSIO_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MDS_READ_META
8 C !INTERFACE:
9 SUBROUTINE MDS_READ_META(
10 I fileName,
11 O simulName,
12 O titleLine,
13 O filePrec,
14 U nDims, nFlds, nTimRec,
15 O dimList, fldList, timList,
16 O misVal, nRecords, fileIter,
17 I useCurrentDir,
18 I myThid )
19
20 C !DESCRIPTION: \bv
21 C *==========================================================*
22 C | S/R MDS_READ_META
23 C | o Read the content of 1 meta file
24 C *==========================================================*
25 C \ev
26
27 C !USES:
28 IMPLICIT NONE
29
30 C == Global variables / common blocks
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "PARAMS.h"
34
35 C !INPUT PARAMETERS:
36 C fileName (string ) :: prefix of meta-file name
37 C nDims (integer) :: max size of array dimList (or =0 if not reading dimList)
38 C nFlds (integer) :: max size of array fldList (or =0 if not reading fldList)
39 C nTimRec (integer) :: max size of array timList (or =0 if not reading timList)
40 C useCurrentDir(logic):: always read from the current directory (even if
41 C "mdsioLocalDir" is set)
42 C myThid (integer) :: my Thread Id number
43 C
44 C !OUTPUT PARAMETERS:
45 C simulName (string) :: name of simulation (recorded in file)
46 C titleLine (string) :: title or any descriptive comments (in file)
47 C filePrec (integer) :: number of bits per word in data-file (32 or 64)
48 C nDims (integer) :: number of dimensions
49 C dimList (integer) :: array of dimensions
50 cC map2gl (integer) :: used for mapping tiled file to global file
51 C nFlds (integer) :: number of fields in "fldList"
52 C fldList (string) :: list of fields (names) stored in file
53 C nTimRec (integer) :: number of time-specification in "timList"
54 C timList (real) :: array of time-specifications (recorded in file)
55 C misVal (real) :: missing value
56 C nRecords (integer) :: number of records
57 C fileIter (integer) :: time-step number (recorded in file)
58 C
59 CHARACTER*(*) fileName
60 CHARACTER*(*) simulName
61 CHARACTER*(*) titleLine
62 INTEGER filePrec
63 INTEGER nDims
64 INTEGER dimList(3,*)
65 c INTEGER map2gl(2)
66 INTEGER nFlds
67 CHARACTER*(8) fldList(*)
68 INTEGER nTimRec
69 _RL timList(*)
70 _RL misVal
71 INTEGER nRecords
72 INTEGER fileIter
73 LOGICAL useCurrentDir
74 INTEGER myThid
75 CEOP
76
77 C !FUNCTIONS
78 INTEGER ILNBLNK
79 EXTERNAL ILNBLNK
80
81 C !LOCAL VARIABLES:
82 C i, j, ii :: loop indices
83 C iG,jG :: global tile indices
84 C iL,pL,iLm :: length of character strings (temp. variables)
85 C nDimFil :: number of dimensions (in meta file)
86 C nFldFil :: number of fields in "fldList" (in meta file)
87 C nTimFil :: number of time-specification in "timList" (meta file)
88 INTEGER i,j,ii
89 INTEGER iG,jG
90 INTEGER iL,pL,iLm
91 INTEGER mUnit, errIO
92 INTEGER nDimFil, nFldFil, nTimFil
93 LOGICAL fileExist, globalFile
94 CHARACTER*(MAX_LEN_MBUF) msgBuf
95 CHARACTER*(MAX_LEN_MBUF) lineBuf
96 CHARACTER*(MAX_LEN_FNAM) mFileName, pfName
97
98 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
99
100 C-- Initialise output arguments
101 simulName = ' '
102 titleLine = ' '
103 filePrec = 0
104 nRecords = 0
105 fileIter = 0
106 c map2gl(1) = 0
107 c map2gl(2) = 1
108 DO j=1,nDims
109 DO i=1,3
110 dimList(i,j) = 0
111 ENDDO
112 ENDDO
113 DO i=1,nFlds
114 fldList(i)= ' '
115 ENDDO
116 DO i=1,nTimRec
117 timList(i) = 0.
118 ENDDO
119 misVal = oneRL
120 C-- Initialise Temp Var.
121 fileExist = .FALSE.
122 globalFile = .FALSE.
123 nDimFil = 0
124 nFldFil = 0
125 nTimFil = 0
126
127 C-- Only Master thread check for file, open & read ; others will
128 C return null argument ; sharing output needs to be done outside
129 C this S/R, using, e.g., common block (+ Master_thread + Barrier)
130 _BEGIN_MASTER( myThid )
131
132 C Assign special directory
133 iL = ILNBLNK(fileName)
134 pL = ILNBLNK( mdsioLocalDir )
135 IF ( useCurrentDir .OR. pL.EQ.0 ) THEN
136 pfName = fileName
137 ELSE
138 WRITE(pfName,'(2A)') mdsioLocalDir(1:pL), fileName(1:iL)
139 ENDIF
140 pL = ILNBLNK( pfName )
141
142 C-- Search for meta file:
143 C- look for meta-file = {fileName}
144 mFileName = fileName(1:iL)
145 iLm = iL
146 c INQUIRE( FILE=mFileName, EXIST=fileExist )
147 IF ( .NOT.fileExist ) THEN
148 C- look for meta-file = {fileName}'.meta'
149 WRITE(mFileName,'(2A)') fileName(1:iL), '.meta'
150 iLm = iL+5
151 INQUIRE( FILE=mFileName, EXIST=fileExist )
152 ENDIF
153 IF ( fileExist ) THEN
154 globalFile = .TRUE.
155 ELSE
156 C- look for meta-file = {fileName}'.{iG}.{jG}.meta'
157 iG = 1+(myXGlobalLo-1)/sNx
158 jG = 1+(myYGlobalLo-1)/sNy
159 WRITE(mFileName,'(2A,I3.3,A,I3.3,A)')
160 & pfName(1:pL),'.',iG,'.',jG,'.meta'
161 iLm = pL+8+5
162 INQUIRE( FILE=mFileName, EXIST=fileExist )
163 ENDIF
164 IF ( .NOT.fileExist ) THEN
165 C- look for meta-file = {fileName}'.001.001.meta'
166 WRITE(mFileName,'(2A,I3.3,A,I3.3,A)')
167 & pfName(1:pL),'.',1,'.',1,'.meta'
168 iLm = pL+8+5
169 INQUIRE( FILE=mFileName, EXIST=fileExist )
170 ENDIF
171 IF ( .NOT.fileExist ) THEN
172 WRITE(msgBuf,'(4A)') 'WARNING >> MDS_READ_META: file: ',
173 & fileName(1:iL), '.meta , ', mFileName(1:iLm)
174 c & fileName(1:iL), ' , ', mFileName(1:iLm)
175 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
176 & SQUEEZE_RIGHT , myThid )
177 WRITE(msgBuf,'(A)')
178 & 'WARNING >> MDS_READ_META: Files DO not exist'
179 CALL PRINT_MESSAGE( msgBuf, errorMessageUnit,
180 & SQUEEZE_RIGHT , myThid )
181 nFldFil = -1
182 ELSE
183
184 C-- File exist
185 IF ( debugLevel .GE. debLevB ) THEN
186 WRITE(msgBuf,'(2A)') ' MDS_READ_META: opening file: ',
187 & mFileName(1:iLm)
188 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
189 & SQUEEZE_RIGHT , myThid)
190 ENDIF
191
192 C- Assign a free unit number as the I/O channel for this subroutine
193 CALL MDSFINDUNIT( mUnit, myThid )
194
195 C- Open meta-file
196 OPEN( mUnit, FILE=mFileName, STATUS='old',
197 & FORM='formatted', IOSTAT=errIO )
198 c write(0,*) 'errIO=',errIO
199 IF ( errIO .NE. 0 ) THEN
200 WRITE(msgBuf,'(A,A)') 'MDS_READ_META: Unable to open file: ',
201 & mFileName(1:iLm)
202 CALL PRINT_ERROR( msgBuf , myThid )
203 STOP 'ABNORMAL END: S/R MDS_READ_META'
204 ENDIF
205
206 C- Read the meta file in the same way as S/R OPEN_COPY_DATA_FILE
207 C (which seems to be works on many platforms):
208 DO WHILE ( .TRUE. )
209 READ( mUnit, FMT='(A)', END=1001 ) lineBuf
210 C-- Extract information from buffer: "lineBuf"
211 iL = ILNBLNK(lineBuf)
212
213 C- Read simulation name (stored in file)
214 IF ( iL.GE.22 .AND. lineBuf(1:14).EQ.' simulation = ' ) THEN
215 ii = LEN(simulName)
216 c IF ( ii.LT.iL-21 ) print 'warning: truncate simulName'
217 ii = MIN(ii+17,iL-4)
218 simulName = lineBuf(18:ii)
219 iL = 0
220 ENDIF
221
222 C- Read the number of dimensions
223 IF ( nDimFil.EQ.0 .AND.
224 & iL.GE.15 .AND. lineBuf(1:9).EQ.' nDims = ' ) THEN
225 READ(lineBuf(12:iL),'(I3)') nDimFil
226 IF ( nDimFil.GT.nDims .AND. nDims.GE.1 ) THEN
227 WRITE(msgBuf,'(2(A,I3),A)') ' MDS_READ_META: nDims=',
228 & nDimFil, ' too large ( >', nDims, ' )'
229 CALL PRINT_ERROR( msgBuf, myThid )
230 STOP 'ABNORMAL END: S/R MDS_READ_META'
231 ENDIF
232 iL = 0
233 ENDIF
234
235 C- Read list of dimensions
236 IF ( nDims.GE.1 .AND. nDimFil.GE.1 .AND.
237 & iL.GE.11 .AND. lineBuf(1:11).EQ.' dimList = ' ) THEN
238 C- For each dimension, read the following:
239 C 1 global size (ie. the size of the global dimension of all files)
240 C 2 global start (ie. the global position of the start of this file)
241 C 3 global end (ie. the global position of the end of this file)
242 DO j=1,nDimFil
243 C- This is to accomodate with the 2 versions of meta file:
244 READ( mUnit, FMT='(A)', END=1001 ) lineBuf
245 ii = ILNBLNK(lineBuf)
246 IF ( ii.LT.20 ) THEN
247 C New version (S/R MDS_WRITE_META, file mdsio_write_meta.F):
248 C small-size domain without starting blanks.
249 READ(lineBuf, FMT='(3(1X,I5))', ERR=1002, END=1002 )
250 & (dimList(i,j),i=1,3)
251 ELSEIF ( ii.LT.30 ) THEN
252 C Old version (S/R MDSWRITEMETA, file mdsio_writemeta.F):
253 C start each line with 10 blanks.
254 READ(lineBuf, FMT='(9X,3(1X,I5))', ERR=1002, END=1002 )
255 & (dimList(i,j),i=1,3)
256 ELSE
257 C New version (S/R MDS_WRITE_META, file mdsio_write_meta.F):
258 C large-size domain without starting blanks.
259 READ(lineBuf, FMT='(3(1X,I10))', ERR=1002, END=1002 )
260 & (dimList(i,j),i=1,3)
261 ENDIF
262 ENDDO
263 READ( mUnit, FMT='(A)', END=1001 ) lineBuf
264 iL = 0
265 ENDIF
266
267 C- only write if different from default:
268 c IF ( map2gl(1).NE.0 .OR. map2gl(2).NE.1 ) THEN
269 c WRITE(mUnit,'(1X,2(A,I5),A)') 'map2glob = [ ',
270 c & map2gl(1),',',map2gl(2),' ];'
271 c ENDIF
272
273 C- Read the precision of the file
274 IF ( iL.GE.20 .AND. lineBuf(1:12).EQ.' dataprec = ' ) THEN
275 IF ( lineBuf(16:22).EQ. 'float32' ) THEN
276 filePrec = precFloat32
277 ELSEIF ( lineBuf(16:22).EQ. 'float64' ) THEN
278 filePrec = precFloat64
279 ELSE
280 WRITE(msgBuf,'(A)') ' MDS_READ_META: invalid dataprec'
281 CALL PRINT_ERROR( msgBuf, myThid )
282 CALL PRINT_ERROR(lineBuf, myThid )
283 STOP 'ABNORMAL END: S/R MDS_READ_META'
284 ENDIF
285 iL = 0
286 ENDIF
287 C- Read (old format) precision of the file
288 IF ( filePrec.EQ.0 .AND.
289 & iL.GE.18 .AND. lineBuf(1:10).EQ.' format = ' ) THEN
290 IF ( lineBuf(14:20).EQ. 'float32' ) THEN
291 filePrec = precFloat32
292 ELSEIF ( lineBuf(14:20).EQ. 'float64' ) THEN
293 filePrec = precFloat64
294 ELSE
295 WRITE(msgBuf,'(A)') ' MDS_READ_META: invalid dataprec'
296 CALL PRINT_ERROR( msgBuf, myThid )
297 CALL PRINT_ERROR(lineBuf, myThid )
298 STOP 'ABNORMAL END: S/R MDS_READ_META'
299 ENDIF
300 iL = 0
301 ENDIF
302
303 C- Read the number of records
304 IF ( nRecords.EQ.0 .AND.
305 & iL.GE.20 .AND. lineBuf(1:12).EQ.' nrecords = ' ) THEN
306 READ(lineBuf(15:iL),'(I5)') nRecords
307 iL = 0
308 ENDIF
309
310 C- Read recorded iteration number
311 IF ( fileIter.EQ.0 .AND. iL.GE.31 .AND.
312 & lineBuf(1:18).EQ.' timeStepNumber = ' ) THEN
313 READ(lineBuf(21:iL),'(I10)') fileIter
314 iL = 0
315 ENDIF
316
317 C- Read list of Time Intervals
318 IF ( nTimFil.EQ.0 .AND.
319 & iL.GE.38 .AND. lineBuf(1:16).EQ.' timeInterval = ' ) THEN
320 C note: format might change once we have a better idea of what will
321 C be the time-information to write.
322 nTimFil = INT((iL-17-3)/20)
323 IF ( nTimRec.GE.1 ) THEN
324 IF ( nTimFil.GT.nTimRec ) THEN
325 WRITE(msgBuf,'(2(A,I6),A)') ' MDS_READ_META: nTimRec=',
326 & nTimFil, ' too large ( >', nTimRec, ' )'
327 CALL PRINT_ERROR( msgBuf, myThid )
328 STOP 'ABNORMAL END: S/R MDS_READ_META'
329 ENDIF
330 READ(lineBuf(18:iL-3),'(1P20E20.12)',ERR=1003)
331 & (timList(i),i=1,nTimFil)
332 ENDIF
333 iL = 0
334 ENDIF
335
336 IF ( iL.GE.8 .AND. lineBuf(1:4).EQ.' /* ' ) THEN
337 IF ( lineBuf(iL-2:iL).EQ.' */' ) THEN
338 C- Read title or comments (ignored by rdmds)
339 ii = LEN(titleLine)
340 c IF ( ii.LT.iL-7 ) print 'warning: truncate titleLine'
341 ii = MIN(ii+4,iL-3)
342 titleLine = lineBuf(5:ii)
343 iL = 0
344 ENDIF
345 ENDIF
346
347 C- Read missing value
348 IF ( misVal.EQ.oneRL .AND. iL.GE.40 .AND.
349 & lineBuf(1:16).EQ.' missingValue = ' ) THEN
350 READ(lineBuf(19:iL),'(1PE21.14)') misVal
351 iL = 0
352 ENDIF
353
354 C- Read number of Fields
355 IF ( nFldFil.EQ.0 .AND.
356 & iL.GE.16 .AND. lineBuf(1:9).EQ.' nFlds = ' ) THEN
357 READ(lineBuf(12:iL),'(I4)') nFldFil
358 IF ( nFldFil.GT.nFlds .AND. nFlds.GE.1 ) THEN
359 WRITE(msgBuf,'(2(A,I6),A)') ' MDS_READ_META: nFlds=',
360 & nFldFil, ' too large ( >', nFlds, ' )'
361 CALL PRINT_ERROR( msgBuf, myThid )
362 STOP 'ABNORMAL END: S/R MDS_READ_META'
363 ENDIF
364 iL = 0
365 ENDIF
366
367 C- Read list of Fields
368 IF ( nFldFil.GE.1 .AND. nFlds.GE.1 .AND.
369 & iL.GE.11 .AND. lineBuf(1:11).EQ.' fldList = ' ) THEN
370 DO j=1,nFldFil,20
371 READ( mUnit, FMT='(20(2X,A8,1X))', ERR=1004, END=1004 )
372 & (fldList(i),i=j,MIN(nFldFil,j+19))
373 ENDDO
374 READ( mUnit, FMT='(A)', END=1001 ) lineBuf
375 iL = 0
376 ENDIF
377
378 C-- End of reading file line per line
379 ENDDO
380 1004 CONTINUE
381 WRITE(msgBuf,'(2(A,I4),A)')
382 & ' MDS_READ_META: error reading Fields: nFlds=',
383 & nFldFil, ' , j=', j
384 CALL PRINT_ERROR( msgBuf, myThid )
385 STOP 'ABNORMAL END: S/R MDS_READ_META'
386 1003 CONTINUE
387 WRITE(msgBuf,'(2(A,I4),A)')
388 & ' MDS_READ_META: error reading Time-Interval: nTimRec=',
389 & nTimFil, ' , iL=', iL
390 CALL PRINT_ERROR( msgBuf, myThid )
391 CALL PRINT_ERROR(lineBuf, myThid )
392 STOP 'ABNORMAL END: S/R MDS_READ_META'
393 1002 CONTINUE
394 WRITE(msgBuf,'(3(A,I3),A)')
395 & ' MDS_READ_META: error reading Dim-List: nDims=',
396 & nDimFil, ' , j=', j, ' , ii=', ii
397 CALL PRINT_ERROR( msgBuf, myThid )
398 CALL PRINT_ERROR(lineBuf, myThid )
399 STOP 'ABNORMAL END: S/R MDS_READ_META'
400 1001 CONTINUE
401
402 C- Close meta-file
403 CLOSE(mUnit)
404
405 C- end if block: file exist
406 ENDIF
407
408 _END_MASTER( myThid )
409
410 C- Update Arguments with values read from file
411 nDims = nDimFil
412 nFlds = nFldFil
413 nTimRec = nTimFil
414
415 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
416
417 RETURN
418 END

  ViewVC Help
Powered by ViewVC 1.1.22