/[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.9 - (show annotations) (download)
Mon Mar 29 03:33:51 2004 UTC (20 years, 2 months ago) by edhill
Branch: MAIN
Changes since 1.8: +21 -15 lines
 o new "poster children" for the API reference:
   - generic_advdiff
   - mnc

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

  ViewVC Help
Powered by ViewVC 1.1.22