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

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

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


Revision 1.3 - (show annotations) (download)
Wed Jan 7 07:29:13 2004 UTC (20 years, 4 months ago) by edhill
Branch: MAIN
Changes since 1.2: +140 -10 lines
 o more functionality: dims, files, vars, attribs, ...
 o "make test" is working

1 C $Header: /u/u3/gcmpack/MITgcm/pkg/mnc/mnc_var.F,v 1.2 2004/01/06 23:19:27 edhill Exp $
2 C $Name: $
3
4 #include "MNC_OPTIONS.h"
5
6 C==================================================================
7
8 SUBROUTINE MNC_VAR_INIT_DBL(
9 I myThid,
10 I fname,
11 I gname,
12 I vname,
13 I fillval )
14
15 implicit none
16 #include "netcdf.inc"
17 #include "mnc_common.h"
18 #include "EEPARAMS.h"
19
20 C Arguments
21 integer myThid
22 character*(*) fname
23 character*(*) gname
24 character*(*) vname
25 _RL fillval
26
27 C Functions
28 integer ILNBLNK
29
30 C Local Variables
31 integer i,j,k, n, indf,indv, fid, nd, ngrid, is,ie, err
32 integer vid, nv
33 character*(MAX_LEN_MBUF) msgbuf
34 integer rids(10), ids(10)
35 integer lenf,leng,lenv
36
37 C Strip trailing spaces
38 lenf = ILNBLNK(fname)
39 leng = ILNBLNK(gname)
40 lenv = ILNBLNK(vname)
41
42 C Check that the file is open
43 CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, indf)
44 IF (indf .LT. 1) THEN
45 write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname,
46 & ''' must be opened first'
47 CALL print_error(msgbuf, mythid)
48 stop 'ABNORMAL END: S/R MNC_VAR_INIT_DBL'
49 ENDIF
50 fid = mnc_f_info(indf,2)
51
52 C Get the grid information
53 ngrid = mnc_f_info(indf,3)
54 IF (ngrid .LT. 1) THEN
55 write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:lenf),
56 & ''' contains NO grids'
57 CALL print_error(msgbuf, mythid)
58 stop 'ABNORMAL END: S/R MNC_VAR_INIT_DBL'
59 ENDIF
60 DO i = 1,ngrid
61 j = 4 + (i-1)*3
62 k = mnc_f_info(indf,j)
63 n = ILNBLNK(mnc_g_names(k))
64 IF ((leng .EQ. n)
65 & .AND. (mnc_g_names(k)(1:n) .EQ. gname(1:n))) THEN
66 is = mnc_f_info(indf,(j+1))
67 ie = mnc_f_info(indf,(j+2))
68 nd = 0
69 DO k = is,ie
70 nd = nd + 1
71 ids(nd) = mnc_fg_ids(indf,k)
72 ENDDO
73 GOTO 10
74 ENDIF
75 ENDDO
76 write(msgbuf,'(5a)') 'MNC ERROR: file ''', fname(1:lenf),
77 & ''' does not contain grid ''', gname(1:leng), ''''
78 CALL print_error(msgbuf, mythid)
79 stop 'ABNORMAL END: S/R MNC_VAR_INIT_DBL'
80 10 CONTINUE
81
82 C Add the variable definition
83 CALL MNC_FILE_REDEF(myThid, fname)
84 err = NF_DEF_VAR(fid, vname, NF_DOUBLE, nd, ids, vid)
85 write(msgbuf,'(5a)') 'defining variable ''', vname(1:lenv),
86 & ''' in file ''', fname(1:lenf), ''''
87 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
88
89 C Success, so save the variable info
90 CALL MNC_GET_NEXT_EMPTY_IND(myThid, MNC_MAX_ID, mnc_v_names, indv)
91 mnc_v_names(indv)(1:lenv) = vname(1:lenv)
92 nv = mnc_fv_ids(indf,1)
93 i = 2 + nv*2
94 j = i + 1
95 mnc_fv_ids(indf,i) = indv
96 mnc_fv_ids(indf,j) = vid
97 mnc_fv_ids(indf,1) = nv + 1
98
99 RETURN
100 END
101
102 C==================================================================
103
104 SUBROUTINE MNC_VAR_ADD_ATTR_STR(
105 I myThid,
106 I fname,
107 I vname,
108 I atname,
109 I sval )
110
111 implicit none
112 #include "netcdf.inc"
113 #include "mnc_common.h"
114 #include "EEPARAMS.h"
115
116 C Arguments
117 integer myThid
118 character*(*) fname
119 character*(*) vname
120 character*(*) atname
121 character*(*) sval
122
123 C Functions
124 integer ILNBLNK
125
126 C Local Variables
127 integer i,j,k, n, nv, indf, fid,vid, err
128 character*(MAX_LEN_MBUF) msgbuf
129 integer lenf,lenv,lenat,lens
130
131 C Strip trailing spaces
132 lenf = ILNBLNK(fname)
133 lenv = ILNBLNK(vname)
134 lenat = ILNBLNK(atname)
135 lens = ILNBLNK(sval)
136
137 C Check that the file is open
138 CALL MNC_GET_IND(myThid, MNC_MAX_ID, fname, mnc_f_names, indf)
139 IF (indf .LT. 1) THEN
140 write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:lenf),
141 & ''' must be opened first'
142 CALL print_error(msgbuf, mythid)
143 stop 'ABNORMAL END: S/R MNC_VAR_ADD_ATTR_STR'
144 ENDIF
145 fid = mnc_f_info(indf,2)
146
147 C Find the vID
148 nv = mnc_fv_ids(indf,1)
149 DO i = 1,nv
150 k = 2*i
151 j = mnc_fv_ids(indf,k)
152 n = ILNBLNK(mnc_v_names(j))
153 IF ((n .EQ. lenv)
154 & .AND. (mnc_v_names(j)(1:n) .EQ. vname(1:n))) THEN
155 k = k + 1
156 vid = mnc_fv_ids(indf,k)
157 GOTO 10
158 ENDIF
159 ENDDO
160 write(msgbuf,'(5a)') 'MNC ERROR: file ''', fname(1:lenf),
161 & ''' does not contain variable ''', vname(1:lenv), ''''
162 CALL print_error(msgbuf, mythid)
163 stop 'ABNORMAL END: S/R MNC_VAR_ADD_ATTR_STR'
164 10 CONTINUE
165
166 C Set the attribute
167 CALL MNC_FILE_REDEF(myThid, fname)
168 err = NF_PUT_ATT_TEXT(fid, vid, atname, lens, sval)
169 write(msgbuf,'(5a)') 'adding attribute ''', atname(1:lenat),
170 & ''' to file ''', fname(1:lenf), ''''
171 CALL MNC_HANDLE_ERR(myThid, err, msgbuf)
172
173 RETURN
174 END
175

  ViewVC Help
Powered by ViewVC 1.1.22