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

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

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


Revision 1.3 - (hide annotations) (download)
Fri May 23 07:22:40 2008 UTC (16 years ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64, checkpoint65, checkpoint60, checkpoint61, checkpoint62, checkpoint63, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65o, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint59r, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61n, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y, HEAD
Changes since 1.2: +2 -2 lines
replace another instance of mnc_common.h with MNC_COMMON.h

1 mlosch 1.3 C $Header: /u/gcmpack/MITgcm/pkg/land/land_mnc_init.F,v 1.2 2005/09/10 20:40:27 edhill Exp $
2 edhill 1.1 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 mlosch 1.3 #include "MNC_COMMON.h"
43 edhill 1.1 #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 edhill 1.2 C Now add the variable definitions
224     CALL MNC_CW_ADD_VNAME(
225     & 'land_groundT','Cen_xy_Hn__Zland__t',4,5,myThid)
226     CALL MNC_CW_ADD_VATTR_TEXT('land_groundT','units','---',myThid)
227    
228     CALL MNC_CW_ADD_VNAME(
229     & 'land_enthalp','Cen_xy_Hn__Zland__t',4,5,myThid)
230     CALL MNC_CW_ADD_VATTR_TEXT('land_enthalp','units','---',myThid)
231    
232     CALL MNC_CW_ADD_VNAME(
233     & 'land_groundW','Cen_xy_Hn__Zland__t',4,5,myThid)
234     CALL MNC_CW_ADD_VATTR_TEXT('land_groundW','units','---',myThid)
235    
236     CALL MNC_CW_ADD_VNAME('land_skinT','Cen_xy_Hn__-__t',3,4,myThid)
237     CALL MNC_CW_ADD_VATTR_TEXT('land_skinT','units','---',myThid)
238     CALL MNC_CW_ADD_VNAME('land_hSnow','Cen_xy_Hn__-__t',3,4,myThid)
239     CALL MNC_CW_ADD_VATTR_TEXT('land_hSnow','units','---',myThid)
240     CALL MNC_CW_ADD_VNAME('land_snAge','Cen_xy_Hn__-__t',3,4,myThid)
241     CALL MNC_CW_ADD_VATTR_TEXT('land_snAge','units','---',myThid)
242     CALL MNC_CW_ADD_VNAME('land_RunOff','Cen_xy_Hn__-__t',3,4,myThid)
243     CALL MNC_CW_ADD_VATTR_TEXT('land_RunOff','units','---',myThid)
244     CALL MNC_CW_ADD_VNAME('land_enRnOf','Cen_xy_Hn__-__t',3,4,myThid)
245     CALL MNC_CW_ADD_VATTR_TEXT('land_enRnOf','units','---',myThid)
246    
247     CALL MNC_CW_ADD_VNAME('land_HeatFx','Cen_xy_Hn__-__t',3,4,myThid)
248     CALL MNC_CW_ADD_VATTR_TEXT('land_HeatFx','units','---',myThid)
249     CALL MNC_CW_ADD_VNAME('land_frWaFx','Cen_xy_Hn__-__t',3,4,myThid)
250     CALL MNC_CW_ADD_VATTR_TEXT('land_frWaFx','units','---',myThid)
251     CALL MNC_CW_ADD_VNAME('land_EnWaFx','Cen_xy_Hn__-__t',3,4,myThid)
252     CALL MNC_CW_ADD_VATTR_TEXT('land_EnWaFx','units','---',myThid)
253    
254 edhill 1.1 #endif /* ALLOW_MNC */
255    
256     RETURN
257     END
258    
259     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|

  ViewVC Help
Powered by ViewVC 1.1.22