/[MITgcm]/MITgcm/pkg/mnc/mnc_file.F
ViewVC logotype

Contents of /MITgcm/pkg/mnc/mnc_file.F

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


Revision 1.12 - (show annotations) (download)
Wed Feb 4 05:45:09 2004 UTC (20 years, 5 months ago) by edhill
Branch: MAIN
CVS Tags: hrcube4, checkpoint52j_post, checkpoint52k_post, checkpoint52j_pre, hrcube_3
Changes since 1.11: +27 -22 lines
 o working (though incomplete) version of the "wrapper":
   - 149 pre-defined grids:
     - all "meaningful" X,Y,Z,T combinations
     - X,Y with or without halos
     - Horiz: centered, U, V, and corner (vorticity) grids
     - Vert: centered or interface
   - just two function calls to write a variable using one of the
     pre-defined grids
 o tile numbering scheme for both cube and XY grids
 o read, write, and append NetCDF files
 o checks for (acceptable) re-definition of dims, grids, and vars
 o numerous small bug fixes
 o warning: the two mnc_model_* files are now broken/obsolete and
   will soon be removed

1 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_file.F,v 1.11 2004/01/31 04:13:09 edhill Exp $
2 C $Name: $
3
4 #include "MNC_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 SUBROUTINE MNC_FILE_CREATE(
9 I myThid,
10 I fname )
11
12 implicit none
13
14 C Arguments
15 integer myThid
16 character*(*) fname
17
18 C Local Variables
19 integer indf
20
21 CALL MNC_FILE_OPEN(myThid, fname, 0, indf)
22
23 RETURN
24 END
25
26 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
27
28 SUBROUTINE MNC_FILE_OPEN(
29 I myThid,
30 I fname,
31 I itype,
32 O indf )
33
34 implicit none
35 #include "netcdf.inc"
36 #include "mnc_common.h"
37 #include "EEPARAMS.h"
38
39 C Arguments
40 integer myThid,indf
41 character*(*) fname
42 integer itype
43 C itype => [ 0=new | 1=append ]
44
45 C Functions
46 integer ILNBLNK
47
48 C Local Variables
49 integer n, err, fid
50 character*(MAX_LEN_MBUF) msgbuf
51
52 C Is the file already open?
53 CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, indf)
54 IF (indf .GT. 0) THEN
55 write(msgbuf,'(3a)') 'MNC_FILE_OPEN ERROR: ''', fname,
56 & ''' is already open -- cannot open twice'
57 CALL print_error(msgbuf, mythid)
58 stop 'ABNORMAL END: package MNC'
59 ENDIF
60
61 write(msgbuf,'(3a)') 'opening ''', fname, ''''
62 IF (itype .EQ. 0) THEN
63
64 C Create new file
65 err = NF_CREATE(fname, NF_CLOBBER, fid)
66 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
67
68 ELSEIF (itype .EQ. 1) THEN
69
70 C Append to existing file
71 CALL MNC_FILE_READALL(myThid, fname)
72
73 ELSE
74 C Error
75 write(msgbuf,'(a,i5,a)') 'MNC_FILE_OPEN ERROR: ''', itype,
76 & ''' is not defined--should be: [0|1]'
77 CALL print_error( msgbuf, mythid )
78 stop 'ABNORMAL END: S/R MNC_FILE_ADD_ATTR_STR'
79 ENDIF
80
81 CALL MNC_GET_NEXT_EMPTY_IND(myThid,MNC_MAX_ID,mnc_f_names,indf)
82 n = ILNBLNK(fname)
83 mnc_f_names(indf)(1:n) = fname(1:n)
84 mnc_f_info(indf,1) = 1
85 mnc_f_info(indf,2) = fid
86 mnc_f_info(indf,3) = 0
87 mnc_fv_ids(indf,1) = 0
88 mnc_f_alld(indf,1) = 0
89
90 RETURN
91 END
92
93 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
94
95 SUBROUTINE MNC_FILE_ADD_ATTR_STR(
96 I myThid,
97 I fname,
98 I atname,
99 I sval )
100
101 implicit none
102 C Arguments
103 integer myThid
104 character*(*) fname, atname, sval
105
106 CALL MNC_FILE_ADD_ATTR_ANY(myThid,fname,atname, 1,
107 & sval, 0, 0.0D0, 0.0, 0 )
108 RETURN
109 END
110
111 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
112
113 SUBROUTINE MNC_FILE_ADD_ATTR_DBL(
114 I myThid,
115 I fname,
116 I atname,
117 I len,
118 I dval )
119
120 implicit none
121 C Arguments
122 integer myThid, len
123 character*(*) fname, atname
124 REAL*8 dval
125
126 CALL MNC_FILE_ADD_ATTR_ANY(myThid,fname,atname, 2,
127 & ' ', len, dval, 0.0, 0 )
128 RETURN
129 END
130
131 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
132
133 SUBROUTINE MNC_FILE_ADD_ATTR_REAL(
134 I myThid,
135 I fname,
136 I atname,
137 I len,
138 I rval )
139
140 implicit none
141 C Arguments
142 integer myThid, len
143 character*(*) fname, atname
144 REAL*4 rval
145
146 CALL MNC_FILE_ADD_ATTR_ANY(myThid,fname,atname, 3,
147 & ' ', len, 0.0D0, rval, 0 )
148 RETURN
149 END
150
151 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
152
153 SUBROUTINE MNC_FILE_ADD_ATTR_INT(
154 I myThid,
155 I fname,
156 I atname,
157 I len,
158 I ival )
159
160 implicit none
161 C Arguments
162 integer myThid, len, ival
163 character*(*) fname, atname
164
165 CALL MNC_FILE_ADD_ATTR_ANY(myThid,fname,atname, 4,
166 & ' ', len, 0.0D0, 0.0, ival )
167 RETURN
168 END
169
170 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
171
172 SUBROUTINE MNC_FILE_ADD_ATTR_ANY(
173 I myThid,
174 I fname,
175 I atname,
176 I atype, sv, len,dv,rv,iv )
177
178 implicit none
179 #include "netcdf.inc"
180 #include "mnc_common.h"
181 #include "EEPARAMS.h"
182
183 C Arguments
184 integer myThid, atype, len, iv
185 character*(*) fname, atname, sv
186 REAL*8 dv
187 REAL*4 rv
188
189 C Functions
190 integer ILNBLNK
191
192 C Local Variables
193 integer n, err, fid, ind, n1, lens
194 character*(MNC_MAX_CHAR) s1
195 character*(MAX_LEN_MBUF) msgbuf
196
197 C Verify that the file is open
198 CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, ind)
199 IF (ind .LT. 0) THEN
200 write(msgbuf,'(3a)') 'MNC ERROR: file ''',
201 & fname, ''' must be opened first'
202 CALL print_error( msgbuf, mythid )
203 stop 'ABNORMAL END: S/R MNC_FILE_ADD_ATTR_INT'
204 ENDIF
205 fid = mnc_f_info(ind,2)
206
207 C Enter define mode
208 CALL MNC_FILE_REDEF(myThid, fname)
209
210 s1(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
211 n1 = ILNBLNK(atname)
212 s1(1:n1) = atname(1:n1)
213
214 IF (atype .EQ. 1) THEN
215 lens = ILNBLNK(sv)
216 err = NF_PUT_ATT_TEXT(fid, NF_GLOBAL, s1, lens, sv)
217 CALL MNC_HANDLE_ERR(myThid, err,
218 & 'adding TEXT attribute in S/R MNC_FILE_ADD_ATTR_ANY')
219 ELSEIF (atype .EQ. 2) THEN
220 err = NF_PUT_ATT_DOUBLE(fid, NF_GLOBAL, s1, NF_DOUBLE, len, dv)
221 CALL MNC_HANDLE_ERR(myThid, err,
222 & 'adding DOUBLE attribute in S/R MNC_FILE_ADD_ATTR_ANY')
223 ELSEIF (atype .EQ. 3) THEN
224 err = NF_PUT_ATT_REAL(fid, NF_GLOBAL, s1, NF_FLOAT, len, rv)
225 CALL MNC_HANDLE_ERR(myThid, err,
226 & 'adding REAL attribute in S/R MNC_FILE_ADD_ATTR_ANY')
227 ELSEIF (atype .EQ. 4) THEN
228 err = NF_PUT_ATT_INT(fid, NF_GLOBAL, s1, NF_INT, len, iv)
229 CALL MNC_HANDLE_ERR(myThid, err,
230 & 'adding INT attribute in S/R MNC_FILE_ADD_ATTR_ANY')
231 ELSE
232 write(msgbuf,'(a,i10,a)') 'MNC ERROR: atype = ''', atype,
233 & ''' is invalid--must be: [1-4]'
234 n = ILNBLNK(msgbuf)
235 CALL print_error(msgbuf(1:n), mythid)
236 stop 'ABNORMAL END: S/R MNC_VAR_ADD_ATTR_ANY'
237 ENDIF
238
239 RETURN
240 END
241
242 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
243
244 SUBROUTINE MNC_FILE_CLOSE(
245 I myThid,
246 I fname )
247
248 implicit none
249 #include "netcdf.inc"
250 #include "mnc_common.h"
251 #include "EEPARAMS.h"
252
253 C Arguments
254 integer myThid
255 character*(*) fname
256
257 C Local Variables
258 integer i,j,k,n, err, fid, ind
259 character*(MAX_LEN_MBUF) msgbuf
260
261 C Check that the file is open
262 CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, ind)
263 IF (ind .LT. 1) THEN
264 write(msgbuf,'(3a)') 'MNC Warning: file ''', fname,
265 & ''' is already closed'
266 CALL print_error( msgbuf, mythid )
267 RETURN
268 ENDIF
269 fid = mnc_f_info(ind,2)
270 err = NF_CLOSE(fid)
271 write(msgbuf,'(3a)') ' cannot close file ''', fname, ''''
272 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
273
274 C Clear all the info associated with this file
275 C variables
276 n = mnc_fv_ids(ind,1)
277 IF (n .GE. 1) THEN
278 DO i = 1,n
279 j = 2 + 3*(i - 1)
280 k = mnc_fv_ids(ind,j)
281 mnc_v_names(k)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
282 ENDDO
283 DO i = 1,(1 + 3*n)
284 mnc_fv_ids(ind,i) = 0
285 ENDDO
286 ENDIF
287 C dims
288 n = mnc_f_alld(ind,1)
289 mnc_f_alld(ind,1) = 0
290 DO i = 1,n
291 j = mnc_f_alld(ind,i+1)
292 mnc_d_ids(j) = 0
293 mnc_d_size(j) = 0
294 mnc_d_names(j)(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
295 mnc_f_alld(ind,i+1) = 0
296 ENDDO
297 C grids
298 n = mnc_f_info(ind,3)
299 IF (n .GT. 0) THEN
300 DO i = 1,n
301 j = 4 + 3*(i - 1)
302 k = mnc_f_info(ind,j)
303 mnc_g_names(k)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
304 ENDDO
305 DO i = 1,MNC_MAX_INFO
306 mnc_fd_ind(ind,i) = 0
307 mnc_f_info(ind,i) = 0
308 ENDDO
309 ENDIF
310 C file name
311 mnc_f_names(ind)(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
312
313 RETURN
314 END
315
316 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
317
318 SUBROUTINE MNC_FILE_CLOSE_ALL_MATCHING(
319 I myThid,
320 I fname )
321
322 implicit none
323 #include "netcdf.inc"
324 #include "mnc_common.h"
325 #include "EEPARAMS.h"
326
327 C Arguments
328 integer myThid
329 character*(*) fname
330
331 C Functions
332 integer ILNBLNK
333
334 C Local Variables
335 integer i,n
336
337 n = ILNBLNK(fname)
338 DO i = 1,MNC_MAX_ID
339
340 C Check that the file is open
341 IF (fname(1:n) .EQ. mnc_f_names(i)(1:n)) THEN
342 CALL MNC_FILE_CLOSE(myThid,mnc_f_names(i))
343 ENDIF
344
345 ENDDO
346
347 RETURN
348 END
349
350 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
351
352 SUBROUTINE MNC_FILE_CLOSE_ALL(
353 I myThid )
354
355 implicit none
356 #include "netcdf.inc"
357 #include "mnc_common.h"
358 #include "EEPARAMS.h"
359
360 C Arguments
361 integer myThid
362
363 C Local Variables
364 integer i
365
366 DO i = 1,MNC_MAX_ID
367
368 C Check that the file is open
369 IF (mnc_f_names(i)(1:MNC_MAX_CHAR)
370 & .NE. mnc_blank_name(1:MNC_MAX_CHAR)) THEN
371 CALL MNC_FILE_CLOSE(myThid,mnc_f_names(i))
372 ENDIF
373
374 ENDDO
375
376 RETURN
377 END
378
379 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
380
381 SUBROUTINE MNC_FILE_REDEF(
382 I myThid,
383 I fname )
384
385 implicit none
386 #include "netcdf.inc"
387 #include "mnc_common.h"
388 #include "EEPARAMS.h"
389
390 C Arguments
391 integer myThid
392 character*(*) fname
393
394 C Functions
395 integer ILNBLNK
396
397 C Local Variables
398 integer ind, fid, def, err, n
399 character*(MAX_LEN_MBUF) msgbuf
400
401 C Verify that the file is open
402 CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, ind)
403 IF (ind .LT. 0) THEN
404 n = ILNBLNK(fname)
405 write(msgbuf,'(3a)') 'MNC ERROR: file ''',
406 & fname(1:n), ''' must be opened first'
407 CALL print_error( msgbuf, mythid )
408 stop 'ABNORMAL END: S/R MNC_FILE_REDEF'
409 ENDIF
410 def = mnc_f_info(ind,1)
411 fid = mnc_f_info(ind,2)
412
413 IF (def .NE. 1) THEN
414 C Enter define mode
415 err = NF_REDEF(fid)
416 CALL MNC_HANDLE_ERR(myThid, err,
417 & 'entering define mode in S/R MNC_FILE_REDEF')
418 mnc_f_info(ind,1) = 1
419 ENDIF
420
421 RETURN
422 END
423
424 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
425
426 SUBROUTINE MNC_FILE_ENDDEF(
427 I myThid,
428 I fname )
429
430 implicit none
431 #include "netcdf.inc"
432 #include "mnc_common.h"
433 #include "EEPARAMS.h"
434
435 C Arguments
436 integer myThid
437 character*(*) fname
438
439 C Functions
440 integer ILNBLNK
441
442 C Local Variables
443 integer ind, fid, def, err, n
444 character*(MAX_LEN_MBUF) msgbuf
445
446 C Verify that the file is open
447 CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, ind)
448 IF (ind .LT. 0) THEN
449 n = ILNBLNK(fname)
450 write(msgbuf,'(3a)') 'MNC ERROR: file ''',
451 & fname(1:n), ''' must be opened first'
452 CALL print_error( msgbuf, mythid )
453 stop 'ABNORMAL END: S/R MNC_FILE_REDEF'
454 ENDIF
455 def = mnc_f_info(ind,1)
456 fid = mnc_f_info(ind,2)
457
458 IF (def .NE. 2) THEN
459 C Enter define mode
460 err = NF_ENDDEF(fid)
461 CALL MNC_HANDLE_ERR(myThid, err,
462 & 'ending define mode in S/R MNC_FILE_ENDDEF')
463 mnc_f_info(ind,1) = 2
464 ENDIF
465
466 RETURN
467 END
468
469 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
470
471 SUBROUTINE MNC_FILE_READALL(
472 I myThid,
473 I fname )
474
475 implicit none
476 #include "netcdf.inc"
477 #include "EEPARAMS.h"
478
479 C Arguments
480 integer myThid
481 character*(*) fname
482
483 C Functions
484 integer IFNBLNK, ILNBLNK
485
486 C Local Variables
487 integer ierr, nff,nlf, indf
488 character*(MAX_LEN_MBUF) msgbuf
489
490 nff = IFNBLNK(fname)
491 nlf = ILNBLNK(fname)
492 CALL MNC_FILE_TRY_READ(myThid, fname, ierr, indf)
493 write(msgbuf,'(3a)') 'MNC ERROR: cannot open file ''',
494 & fname(nff:nlf), ''' for read/write access'
495 CALL MNC_HANDLE_ERR(myThid, ierr, msgbuf)
496
497 RETURN
498 END
499
500 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
501
502 SUBROUTINE MNC_FILE_TRY_READ(
503 I myThid,
504 I fname,
505 O ierr,
506 O indf )
507
508 implicit none
509 #include "netcdf.inc"
510 #include "mnc_common.h"
511 #include "EEPARAMS.h"
512
513 C Arguments
514 integer myThid, ierr, indf
515 character*(*) fname
516
517 C Functions
518 integer IFNBLNK, ILNBLNK
519
520 C Local Variables
521 integer i,j,k, fid, err, ndim,nvar,ngat,unlimid
522 integer dlen, id, xtype, nat, nff,nlf, iv
523 integer ndv, did, ns,ne, n1,n2, indg, indv
524 character*(MAX_LEN_MBUF) msgbuf
525 character*(NF_MAX_NAME) name
526 integer idlist(NF_MAX_VAR_DIMS)
527 character*(MNC_MAX_CHAR) dnames(20)
528
529 C Open and save the filename and fID
530 nff = IFNBLNK(fname)
531 nlf = ILNBLNK(fname)
532 err = NF_OPEN(fname, NF_WRITE, fid)
533 ierr = NF_NOERR
534 IF (err .NE. NF_NOERR) THEN
535 ierr = err
536 RETURN
537 ENDIF
538 CALL MNC_GET_NEXT_EMPTY_IND(myThid,MNC_MAX_ID,mnc_f_names,indf)
539 mnc_f_names(indf)(1:(nlf-nff+1)) = fname(nff:nlf)
540 mnc_f_info(indf,2) = fid
541
542 C Get the overall number of entities
543 err = NF_INQ(fid, ndim, nvar, ngat, unlimid)
544 write(msgbuf,'(4a)') 'MNC ERROR: cannot read number of dims',
545 & ' in file ''', fname(nff:nlf), ''''
546 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
547
548 C Read each dimension and save the information
549 DO id = 1,ndim
550 err = NF_INQ_DIM(fid, id, name, dlen)
551 write(msgbuf,'(2a,i5,3a)') 'MNC ERROR: cannot read dimension',
552 & ' info for dim ''', id, ''' in file ''',
553 & fname(nff:nlf), ''''
554 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
555 IF (id .EQ. unlimid) THEN
556 dlen = -1
557 ENDIF
558 ns = IFNBLNK(name)
559 ne = ILNBLNK(name)
560 CALL MNC_DIM_INIT_ALL(myThid,fname,name(ns:ne),dlen,'N')
561 DO i = 1,mnc_f_alld(indf,1)
562 j = mnc_f_alld(indf,i+1)
563 n1 = IFNBLNK(mnc_d_names(j))
564 n2 = ILNBLNK(mnc_d_names(j))
565 IF (((ne-ns) .EQ. (n2-n1))
566 & .AND. (mnc_d_names(j)(ns:ne) .EQ. name(ns:ne))) THEN
567 mnc_d_ids(j) = id
568 goto 10
569 ENDIF
570 ENDDO
571 10 CONTINUE
572 ENDDO
573
574 C Read and save each variable
575 DO id = 1,nvar
576 err = NF_INQ_VAR(fid, id, name, xtype, ndv, idlist, nat)
577 write(msgbuf,'(2a,i5,3a)') 'MNC ERROR: cannot read variable',
578 & ' info for variable ''', id, ''' in file ''',
579 & fname(nff:nlf), ''''
580 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
581 n1 = IFNBLNK(name)
582 n2 = ILNBLNK(name)
583
584 C Create a grid for this variable
585 DO i = 1,ndv
586 did = idlist(i)
587 dnames(i)(1:MNC_MAX_CHAR) = mnc_d_names(did)(1:MNC_MAX_CHAR)
588 ENDDO
589 CALL MNC_GRID_INIT_ALL(myThid, fname, name, ndv, dnames, indg)
590
591 C Update the tables
592 CALL MNC_GET_NEXT_EMPTY_IND(myThid,MNC_MAX_ID,mnc_v_names,indv)
593 mnc_v_names(indv)(1:(n2-n1+1)) = name(n1:n2)
594 iv = 2 + 3*mnc_fv_ids(indf,1)
595 mnc_fv_ids(indf,iv) = indv
596 mnc_fv_ids(indf,iv+1) = id
597 DO i = 1,mnc_f_info(indf,3)
598 j = 4 + 3*(i-1)
599 k = mnc_f_info(indf,j)
600 IF (k .EQ. indg) THEN
601 mnc_fv_ids(indf,iv+2) = j
602 GOTO 20
603 ENDIF
604 ENDDO
605 20 CONTINUE
606 mnc_fv_ids(indf,1) = mnc_fv_ids(indf,1) + 1
607
608 ENDDO
609
610 RETURN
611 END
612

  ViewVC Help
Powered by ViewVC 1.1.22