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

Annotation of /MITgcm/pkg/mnc/mnc_cw_init.F

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


Revision 1.3 - (hide annotations) (download)
Wed Feb 23 05:17:36 2005 UTC (19 years, 4 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint58w_post, checkpoint57m_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint57e_post, checkpoint58n_post, checkpoint58x_post, checkpoint57g_pre, checkpoint58t_post, checkpoint58h_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint57r_post, checkpoint59, checkpoint58, eckpoint57e_pre, checkpoint57h_done, checkpoint58f_post, checkpoint57x_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint57f_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58g_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.2: +29 -8 lines
 o add more "Z" dimensions and associated coordinate vars to MNC

1 edhill 1.3 C $Header: /u/gcmpack/MITgcm/pkg/mnc/mnc_cw_init.F,v 1.2 2004/12/17 21:28:25 edhill Exp $
2 edhill 1.1 C $Name: $
3    
4     #include "MNC_OPTIONS.h"
5    
6     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
7     CBOP 0
8     C !ROUTINE: MNC_CW_INIT
9    
10     C !INTERFACE:
11     SUBROUTINE MNC_CW_INIT(
12     I sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr,
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    
40     C !USES:
41     implicit none
42     #include "mnc_common.h"
43     #include "EEPARAMS.h"
44    
45     C !INPUT PARAMETERS:
46     integer myThid
47     integer sNx,sNy, OLx,OLy, nSx,nSy, nPx,nPy, Nr
48     CEOP
49    
50     C !LOCAL VARIABLES:
51     integer CW_MAX_LOC
52 edhill 1.3 parameter ( CW_MAX_LOC = 6 )
53 edhill 1.1 integer i, ihorz,ihsub,ivert,itime,ihalo, is,ih, n,ntot
54     integer ndim, ncomb, nvch
55     character*(MNC_MAX_CHAR) name
56     character*(MNC_MAX_CHAR) dn(CW_MAX_LOC)
57     character*(5) horz_dat(CW_MAX_LOC), hsub_dat(CW_MAX_LOC),
58     & vert_dat(CW_MAX_LOC), time_dat(CW_MAX_LOC),
59     & halo_dat(CW_MAX_LOC)
60     integer dim(CW_MAX_LOC), ib(CW_MAX_LOC), ie(CW_MAX_LOC)
61    
62     C Functions
63     integer ILNBLNK
64     external ILNBLNK
65    
66     C ......12345....12345....12345....12345....12345...
67     data horz_dat /
68 edhill 1.3 & '- ', 'U ', 'V ', 'Cen ', 'Cor ', ' ' /
69 edhill 1.1 data hsub_dat /
70 edhill 1.3 & 'xy ', 'x ', 'y ', '- ', ' ', ' ' /
71 edhill 1.1 data halo_dat /
72 edhill 1.3 & 'Hn ', 'Hy ', '-- ', ' ', ' ', ' ' /
73 edhill 1.1 data vert_dat /
74 edhill 1.3 & '- ', 'C ', 'I ', 'L ', 'U ', 'S ' /
75 edhill 1.1 data time_dat /
76 edhill 1.3 & '- ', 't ', ' ', ' ', ' ', ' ' /
77 edhill 1.1
78 edhill 1.2 C Create the types
79 edhill 1.1 ncomb = 0
80     DO ihorz = 1,5
81     DO is = 1,3
82     DO ih = 1,2
83    
84     C Loop just ONCE if the Horiz component is "-"
85     ihsub = is
86     ihalo = ih
87     IF (ihorz .EQ. 1) THEN
88     IF ((is .EQ. 1) .AND. (ih .EQ. 1)) THEN
89     ihsub = 4
90     ihalo = 3
91     ELSE
92     GOTO 10
93     ENDIF
94     ENDIF
95    
96 edhill 1.3 DO ivert = 1,6
97 edhill 1.1 DO itime = 1,2
98    
99     C horiz and hsub
100     name(1:MNC_MAX_CHAR) = mnc_blank_name(1:MNC_MAX_CHAR)
101     n = ILNBLNK(horz_dat(ihorz))
102     name(1:n) = horz_dat(ihorz)(1:n)
103     ntot = n + 1
104     name(ntot:ntot) = '_'
105     n = ILNBLNK(hsub_dat(ihsub))
106     name((ntot+1):(ntot+n)) = hsub_dat(ihsub)(1:n)
107     ntot = ntot + n
108    
109     C halo, vert, and time
110     write(name((ntot+1):(ntot+5)), '(a1,2a2)')
111     & '_', halo_dat(ihalo)(1:2), '__'
112     nvch = ILNBLNK(vert_dat(ivert))
113     n = ntot+6+nvch-1
114     name((ntot+6):(n)) = vert_dat(ivert)(1:nvch)
115     write(name((n+1):(n+3)), '(a2,a1)')
116     & '__', time_dat(itime)(1:1)
117    
118     ndim = 0
119     DO i = 1,CW_MAX_LOC
120     dn(i)(1:MNC_MAX_CHAR)=mnc_blank_name(1:MNC_MAX_CHAR)
121     dim(i) = 0
122     ib(i) = 0
123     ie(i) = 0
124     ENDDO
125    
126     C Horizontal dimensions
127     IF (halo_dat(ihalo)(1:5) .EQ. 'Hn ') THEN
128    
129     IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
130     ndim = ndim + 1
131     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
132     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
133     dn(ndim)(1:1) = 'X'
134     dim(ndim) = sNx + 2*OLx
135     ib(ndim) = OLx + 1
136     ie(ndim) = OLx + sNx
137     ENDIF
138     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
139     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
140     dn(ndim)(1:3) = 'Xp1'
141     dim(ndim) = sNx + 2*OLx
142     ib(ndim) = OLx + 1
143     ie(ndim) = OLx + sNx + 1
144     ENDIF
145     ENDIF
146     IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
147     & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
148     ndim = ndim + 1
149     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cen')
150     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'U') ) THEN
151     dn(ndim)(1:1) = 'Y'
152     dim(ndim) = sNy + 2*OLy
153     ib(ndim) = OLy + 1
154     ie(ndim) = OLy + sNy
155     ENDIF
156     IF ( (horz_dat(ihorz)(1:3) .EQ. 'Cor')
157     & .OR. (horz_dat(ihorz)(1:1) .EQ. 'V') ) THEN
158     dn(ndim)(1:3) = 'Yp1'
159     dim(ndim) = sNy + 2*OLy
160     ib(ndim) = OLy + 1
161     ie(ndim) = OLy + sNy + 1
162     ENDIF
163     ENDIF
164    
165     ELSEIF (halo_dat(ihalo)(1:5) .EQ. 'Hy ') THEN
166    
167     IF (hsub_dat(ihsub)(1:1) .EQ. 'x') THEN
168     ndim = ndim + 1
169     dn(ndim)(1:3) = 'Xwh'
170     dim(ndim) = sNx + 2*OLx
171     ib(ndim) = 1
172     ie(ndim) = sNx + 2*OLx
173     ENDIF
174     IF ((hsub_dat(ihsub)(1:1) .EQ. 'y')
175     & .OR. (hsub_dat(ihsub)(2:2) .EQ. 'y')) THEN
176     ndim = ndim + 1
177     dn(ndim)(1:3) = 'Ywh'
178     dim(ndim) = sNy + 2*OLy
179     ib(ndim) = 1
180     ie(ndim) = sNy + 2*OLy
181     ENDIF
182    
183     ENDIF
184    
185     C Vertical dimension
186     IF (vert_dat(ivert)(1:1) .EQ. 'C') THEN
187     ndim = ndim + 1
188     dn(ndim)(1:1) = 'Z'
189     dim(ndim) = Nr
190     ib(ndim) = 1
191     ie(ndim) = Nr
192     ENDIF
193     IF (vert_dat(ivert)(1:1) .EQ. 'I') THEN
194     ndim = ndim + 1
195     dn(ndim)(1:3) = 'Zp1'
196     dim(ndim) = Nr + 1
197     ib(ndim) = 1
198     ie(ndim) = Nr + 1
199     ENDIF
200 edhill 1.3 IF (vert_dat(ivert)(1:1) .EQ. 'L') THEN
201     ndim = ndim + 1
202     dn(ndim)(1:2) = 'Zl'
203     dim(ndim) = Nr
204     ib(ndim) = 1
205     ie(ndim) = Nr
206     ENDIF
207     IF (vert_dat(ivert)(1:1) .EQ. 'U') THEN
208     ndim = ndim + 1
209     dn(ndim)(1:2) = 'Zu'
210     dim(ndim) = Nr
211     ib(ndim) = 1
212     ie(ndim) = Nr
213     ENDIF
214     IF (vert_dat(ivert)(1:1) .EQ. 'M') THEN
215     ndim = ndim + 1
216     dn(ndim)(1:3) = 'Zm1'
217     dim(ndim) = Nr - 1
218     ib(ndim) = 1
219     ie(ndim) = Nr - 1
220     ENDIF
221 edhill 1.1
222     C Time dimension
223     IF (time_dat(itime)(1:1) .EQ. 't') THEN
224     ndim = ndim + 1
225     dn(ndim)(1:1) = 'T'
226     dim(ndim) = -1
227     ib(ndim) = 1
228     ie(ndim) = 1
229     ENDIF
230    
231     IF (ndim .GT. 0) THEN
232     #ifdef MNC_DEBUG
233     ncomb = ncomb + 1
234     write(*,'(i4,a3,a15,i3,a3,5i4,a4,5i4,a4,5i4,6a4)')
235     & ncomb, ' : ', name(1:15), ndim,
236     & ' : ', (dim(i), i=1,5),
237     & ' | ', (ib(i), i=1,5),
238     & ' | ', (ie(i), i=1,5),
239     & ' | ', (dn(i)(1:4), i=1,5)
240     #endif
241    
242     CALL MNC_CW_ADD_GNAME(name, ndim,
243     & dim, dn, ib, ie, myThid)
244     ENDIF
245    
246     ENDDO
247     ENDDO
248    
249     10 CONTINUE
250     ENDDO
251     ENDDO
252     ENDDO
253    
254     RETURN
255     END
256    
257     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22