/[MITgcm]/MITgcm/pkg/land/land_mnc_init.F
ViewVC logotype

Contents of /MITgcm/pkg/land/land_mnc_init.F

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


Revision 1.1 - (show annotations) (download)
Fri Jul 9 03:17:44 2004 UTC (19 years, 10 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint57o_post, checkpoint57m_post, checkpoint55c_post, checkpoint54e_post, checkpoint57k_post, checkpoint55d_pre, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57e_post, checkpoint55h_post, checkpoint57g_pre, checkpoint55b_post, checkpoint54d_post, checkpoint56c_post, checkpoint55, checkpoint57f_pre, checkpoint57a_post, checkpoint54f_post, checkpoint55g_post, checkpoint55f_post, checkpoint57r_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57h_done, checkpoint57n_post, checkpoint57p_post, checkpoint57f_post, checkpoint57q_post, checkpoint57c_post, checkpoint55e_post, checkpoint55a_post, checkpoint54c_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
 o add mnc grid types for the land ("land_nLev") package
 o mnc initialization is done at the end of land_readparms
 o compiled, tested, and run with g77

1 C $Header: $
2 C $Name: $
3
4 #include "LAND_OPTIONS.h"
5
6 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7 CBOP 0
8 C !ROUTINE: LAND_MNC_INIT
9
10 C !INTERFACE:
11 SUBROUTINE LAND_MNC_INIT(
12 I sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nland_lev,
13 I myThid )
14
15 C !DESCRIPTION:
16 C Create the pre-defined grid types and variable types.
17
18 C The grid type is a character string that encodes the presence and
19 C types associated with the four possible dimensions. The character
20 C string follows the format
21 C \begin{center}
22 C \texttt{H0\_H1\_H2\_\_V\_\_T}
23 C \end{center}
24 C where the terms \textit{H0}, \textit{H1}, \textit{H2}, \textit{V},
25 C \textit{T} can be almost any combination of the following:
26 C \begin{center}
27 C \begin{tabular}[h]{|ccc|c|c|}\hline
28 C \multicolumn{3}{|c|}{Horizontal} & Vertical & Time \\
29 C \textit{H0}: location & \textit{H1}: dimensions & \textit{H2}: halo
30 C & \textit{V}: location & \textit{T}: level \\\hline
31 C \texttt{-} & xy & Hn & \texttt{-} & \texttt{-} \\
32 C U & x & Hy & i & t \\
33 C V & y & & c & \\
34 C Cen & & & & \\
35 C Cor & & & & \\\hline
36 C \end{tabular}
37 C \end{center}
38
39 C !USES:
40 implicit none
41 #ifdef ALLOW_MNC
42 #include "mnc_common.h"
43 #endif /* ALLOW_MNC */
44 #include "EEPARAMS.h"
45
46 C !INPUT PARAMETERS:
47 integer myThid
48 integer sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy
49 integer Nland_lev
50 CEOP
51
52 #ifdef ALLOW_MNC
53
54 C !LOCAL VARIABLES:
55 integer CW_MAX_LOC
56 parameter ( CW_MAX_LOC = 5 )
57 integer i, ihorz,ihsub,ivert,itime,ihalo, is,ih, n,ntot
58 integer ndim, ncomb, nvch
59 character*(MNC_MAX_CHAR) name
60 character*(MNC_MAX_CHAR) dn(CW_MAX_LOC)
61 character*(5) horz_dat(CW_MAX_LOC), hsub_dat(CW_MAX_LOC),
62 & vert_dat(CW_MAX_LOC), time_dat(CW_MAX_LOC),
63 & halo_dat(CW_MAX_LOC)
64 integer dim(CW_MAX_LOC), ib(CW_MAX_LOC), ie(CW_MAX_LOC)
65
66 C Functions
67 integer ILNBLNK
68 external ILNBLNK
69
70 C ......12345....12345....12345....12345....12345...
71 data horz_dat /
72 & '- ', 'U ', 'V ', 'Cen ', 'Cor ' /
73 data hsub_dat /
74 & 'xy ', 'x ', 'y ', '- ', ' ' /
75 data halo_dat /
76 & 'Hn ', 'Hy ', '-- ', ' ', ' ' /
77 data vert_dat /
78 & 'Zland', ' ', ' ', ' ', ' ' /
79 data time_dat /
80 & '- ', 't ', ' ', ' ', ' ' /
81
82
83 ncomb = 0
84 DO ihorz = 1,5
85 DO is = 1,3
86 DO ih = 1,2
87
88 C Loop just ONCE if the Horiz component is "-"
89 ihsub = is
90 ihalo = ih
91 IF (ihorz .EQ. 1) THEN
92 IF ((is .EQ. 1) .AND. (ih .EQ. 1)) THEN
93 ihsub = 4
94 ihalo = 3
95 ELSE
96 GOTO 10
97 ENDIF
98 ENDIF
99
100 DO ivert = 1,1
101 DO itime = 1,2
102
103 C horiz and hsub
104 name(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
105 n = ILNBLNK(horz_dat(ihorz))
106 name(1:n) = horz_dat(ihorz)(1:n)
107 ntot = n + 1
108 name(ntot:ntot) = '_'
109 n = ILNBLNK(hsub_dat(ihsub))
110 name((ntot+1):(ntot+n)) = hsub_dat(ihsub)(1:n)
111 ntot = ntot + n
112
113 C halo, vert, and time
114 write(name((ntot+1):(ntot+5)), '(a1,2a2)')
115 & '_', halo_dat(ihalo)(1:2), '__'
116 nvch = ILNBLNK(vert_dat(ivert))
117 n = ntot+6+nvch-1
118 name((ntot+6):(n)) = vert_dat(ivert)(1:nvch)
119 write(name((n+1):(n+3)), '(a2,a1)')
120 & '__', time_dat(itime)(1:1)
121
122 ndim = 0
123 DO i = 1,CW_MAX_LOC
124 dn(i)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
125 dim(i) = 0
126 ib(i) = 0
127 ie(i) = 0
128 ENDDO
129
130 C Horizontal dimensions
131 IF (halo_dat(ihalo)(1:5) .EQ. 'Hn ') THEN
132
133 IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
134 ndim = ndim + 1
135 IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
136 & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
137 dn(ndim)(1:1) = 'X'
138 dim(ndim) = sNx + 2*OLx
139 ib(ndim) = OLx + 1
140 ie(ndim) = OLx + sNx
141 ENDIF
142 IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
143 & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
144 dn(ndim)(1:3) = 'Xp1'
145 dim(ndim) = sNx + 2*OLx
146 ib(ndim) = OLx + 1
147 ie(ndim) = OLx + sNx + 1
148 ENDIF
149 ENDIF
150 IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
151 & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
152 ndim = ndim + 1
153 IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
154 & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
155 dn(ndim)(1:1) = 'Y'
156 dim(ndim) = sNy + 2*OLy
157 ib(ndim) = OLy + 1
158 ie(ndim) = OLy + sNy
159 ENDIF
160 IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
161 & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
162 dn(ndim)(1:3) = 'Yp1'
163 dim(ndim) = sNy + 2*OLy
164 ib(ndim) = OLy + 1
165 ie(ndim) = OLy + sNy + 1
166 ENDIF
167 ENDIF
168
169 ELSEIF (halo_dat(ihalo)(1:5) .EQ. 'Hy ') THEN
170
171 IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
172 ndim = ndim + 1
173 dn(ndim)(1:3) = 'Xwh'
174 dim(ndim) = sNx + 2*OLx
175 ib(ndim) = 1
176 ie(ndim) = sNx + 2*OLx
177 ENDIF
178 IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
179 & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
180 ndim = ndim + 1
181 dn(ndim)(1:3) = 'Ywh'
182 dim(ndim) = sNy + 2*OLy
183 ib(ndim) = 1
184 ie(ndim) = sNy + 2*OLy
185 ENDIF
186
187 ENDIF
188
189 C Vertical dimension
190 IF (vert_dat(ivert)(1:5) .EQ. 'Zland') THEN
191 ndim = ndim + 1
192 dn(ndim)(1:5) = 'Zland'
193 dim(ndim) = Nland_lev
194 ib(ndim) = 1
195 ie(ndim) = Nland_lev
196 ENDIF
197
198 C Time dimension
199 IF ( (time_dat(itime)(1:1) .EQ. 't')
200 & .and. (ndim .ne. 0) ) THEN
201 ndim = ndim + 1
202 dn(ndim)(1:1) = 'T'
203 dim(ndim) = -1
204 ib(ndim) = 1
205 ie(ndim) = 1
206 ENDIF
207
208 IF (ndim .GT. 0) THEN
209
210 CALL MNC_CW_ADD_GNAME(name, ndim,
211 & dim, dn, ib, ie, myThid)
212
213 ENDIF
214
215 ENDDO
216 ENDDO
217
218 10 CONTINUE
219 ENDDO
220 ENDDO
221 ENDDO
222
223 #endif /* ALLOW_MNC */
224
225 RETURN
226 END
227
228 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22