/[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.10 - (show annotations) (download)
Tue Jan 27 05:47:32 2004 UTC (20 years, 4 months ago) by edhill
Branch: MAIN
Changes since 1.9: +14 -14 lines
 o first steps towards a "convenience wrapper" for pre-defined grid types
 o small clean-ups

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

  ViewVC Help
Powered by ViewVC 1.1.22