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

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

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


Revision 1.8 - (show annotations) (download)
Sun Mar 28 19:28:34 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
Changes since 1.7: +19 -3 lines
 o add '*.tex' files to the list used to generate the API documentation
   - add examples of the above to generic_advdiff and mnc
 o temporarily remove eesupp from dir_list since the formatting of
    the comments in those files needs much work

1 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_dim.F,v 1.7 2004/03/19 03:28:36 edhill Exp $
2 C $Name: $
3
4 #include "MNC_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7
8 CBOP
9 C !ROUTINE: MNC_DIM_INIT
10 C !INTERFACE:
11 SUBROUTINE MNC_DIM_INIT(
12 I fname,
13 I dname,
14 I dlen,
15 I myThid )
16
17 C !DESCRIPTION:
18 C Creates a NetCDF dimension within an existing NetCDF file
19
20 C !INPUT PARAMETERS:
21 C Arguments
22 integer myThid, dlen
23 character*(*) fname, dname
24 CEOP
25
26 CALL MNC_DIM_INIT_ALL(fname, dname, dlen, 'Y', myThid)
27
28 RETURN
29 END
30
31
32 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
33
34 CBOP
35 C !ROUTINE: MNC_DIM_INIT_ALL
36 C !INTERFACE:
37 SUBROUTINE MNC_DIM_INIT_ALL(
38 I fname,
39 I dname,
40 I dlen,
41 I doWrite,
42 I myThid )
43
44 C !DESCRIPTION:
45 C Creates a NetCDF dimension within an existing NetCDF file
46
47 C !USES:
48 implicit none
49 #include "netcdf.inc"
50 #include "mnc_common.h"
51 #include "EEPARAMS.h"
52
53 C !INPUT PARAMETERS:
54 integer myThid, dlen
55 character*(*) fname, dname
56 character*(1) doWrite
57
58 C Functions
59 integer ILNBLNK, IFNBLNK
60
61 C !LOCAL VARIABLES:
62 integer i,j, indf,indd, n,nf, dnf,dnl, ntmp, idd, err, tlen
63 character*(MAX_LEN_MBUF) msgbuf
64 CEOP
65
66 nf = ILNBLNK(fname)
67
68 dnf = IFNBLNK(dname)
69 dnl = ILNBLNK(dname)
70
71 C Verify that the file exists
72 CALL MNC_GET_IND(MNC_MAX_ID, fname, mnc_f_names, indf, myThid)
73 IF ( indf .LT. 1 ) THEN
74 write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:nf),
75 & ''' does not exist'
76 CALL print_error( msgbuf, mythid )
77 stop 'ABNORMAL END: S/R MNC_DIM_INIT'
78 ENDIF
79
80 C Verify that the dim is not currently defined within the file
81 n = mnc_f_alld(indf,1)
82 DO i = 1,n
83 j = mnc_f_alld(indf,i+1)
84 ntmp = ILNBLNK(mnc_d_names(j))
85 IF ((ntmp .EQ. (dnl-dnf+1))
86 & .AND. (dname(dnf:dnl) .EQ. mnc_d_names(j)(1:ntmp))) THEN
87 IF (mnc_d_size(j) .NE. dlen) THEN
88 IF ((mnc_d_size(j) .GT. 0) .OR. (dlen .GT. 0)) THEN
89 write(msgbuf,'(5a)') 'MNC ERROR: dimension ''',
90 & dname(dnf:dnl), ''' already exists within file ''',
91 & fname(1:nf), ''' and its size cannot be changed'
92 CALL print_error(msgbuf, mythid)
93 stop 'ABNORMAL END: S/R MNC_DIM_INIT'
94 ELSE
95 C Its OK, the names are the same and both are specifying the
96 C unlimited dimension
97 RETURN
98 ENDIF
99 ELSE
100 C Its OK, the names and sizes are identical
101 RETURN
102 ENDIF
103 ENDIF
104 ENDDO
105
106 CALL MNC_GET_NEXT_EMPTY_IND(MNC_MAX_ID, mnc_d_names, indd, myThid)
107
108 C Create the dim within the file
109 IF (doWrite(1:1) .EQ. 'Y') THEN
110
111 tlen = dlen
112 IF (dlen .LT. 1) tlen = NF_UNLIMITED
113
114 CALL MNC_FILE_REDEF(fname, myThid)
115 err = NF_DEF_DIM(mnc_f_info(indf,2), dname(dnf:dnl), tlen, idd)
116 write(msgbuf,'(5a)') 'MNC_DIM_INIT ERROR: cannot create ',
117 & 'dim ''', dname(dnf:dnl), ''' in file ''', fname(1:nf)
118 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
119
120 ENDIF
121
122 C Add to tables
123 mnc_d_names(indd)(1:(dnl-dnf+1)) = dname(dnf:dnl)
124 mnc_d_size(indd) = dlen
125 mnc_d_ids(indd) = idd
126 mnc_f_alld(indf,1) = n + 1
127 mnc_f_alld(indf,n+2) = indd
128
129 RETURN
130 END
131
132 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
133
134 SUBROUTINE MNC_DIM_UNLIM_SIZE(
135 I fname,
136 I unlim_sz,
137 I myThid )
138
139 implicit none
140 #include "netcdf.inc"
141 #include "mnc_common.h"
142 #include "EEPARAMS.h"
143
144 C Arguments
145 integer myThid, unlim_sz
146 character*(*) fname
147
148 C Functions
149 integer ILNBLNK, IFNBLNK
150
151 C Local Variables
152 integer i,j, nf, indf, fid, unlimid, err
153 character*(MAX_LEN_MBUF) msgbuf
154
155 nf = ILNBLNK(fname)
156
157 C Verify that the file exists
158 CALL MNC_GET_IND(MNC_MAX_ID, fname, mnc_f_names, indf, myThid)
159 IF (indf .LT. 1) THEN
160 write(msgbuf,'(3a)') 'MNC ERROR: file ''', fname(1:nf),
161 & ''' does not exist'
162 CALL print_error(msgbuf, mythid)
163 stop 'ABNORMAL END: S/R MNC_DIM_UNLIM_SIZE'
164 ENDIF
165 fid = mnc_f_info(indf,2)
166
167 C Find the unlimited dim and its current size
168 unlim_sz = -1
169 DO i = 1,mnc_f_alld(indf,1)
170 j = mnc_f_alld(indf,i+1)
171 IF (mnc_d_size(j) .EQ. -1) THEN
172 unlimid = mnc_d_ids(j)
173 err = NF_INQ_DIMLEN(fid, unlimid, unlim_sz)
174 write(msgbuf,'(3a)') 'MNC_DIM_UNLIM_SIZE ERROR: cannot ',
175 & 'determine unlimited dim size in file ''', fname(1:nf)
176 CALL MNC_HANDLE_ERR(err, msgbuf, myThid)
177 RETURN
178 ENDIF
179 ENDDO
180
181 RETURN
182 END
183
184
185 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
186

  ViewVC Help
Powered by ViewVC 1.1.22