/[MITgcm]/MITgcm/model/src/convective_adjustment_ini.F
ViewVC logotype

Contents of /MITgcm/model/src/convective_adjustment_ini.F

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


Revision 1.14 - (show annotations) (download)
Wed Dec 17 05:24:16 2003 UTC (20 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, hrcube5, checkpoint52j_pre, checkpoint54d_post, checkpoint54e_post, checkpoint52l_post, checkpoint52k_post, checkpoint54, checkpoint53, checkpoint52f_post, checkpoint54f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_pre, checkpoint52e_post, checkpoint53d_post, checkpoint54b_post, checkpoint52m_post, checkpoint52f_pre, checkpoint54a_pre, checkpoint53c_post, checkpoint54a_post, checkpoint53a_post, checkpoint53g_post, checkpoint52i_post, checkpoint52h_pre, checkpoint53f_post, checkpoint52j_post, checkpoint52n_post, checkpoint53b_pre, checkpoint53b_post, checkpoint53d_pre, checkpoint54c_post
Changes since 1.13: +1 -13 lines
Patrick says: "we should remove those lines" and I agree.

1 C $Header: /u/gcmpack/MITgcm/model/src/convective_adjustment_ini.F,v 1.13 2003/10/09 04:19:18 edhill Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: CONVECTIVE_ADJUSTMENT_INI
9 C !INTERFACE:
10 SUBROUTINE CONVECTIVE_ADJUSTMENT_INI(
11 I bi, bj, iMin, iMax, jMin, jMax,
12 I myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | SUBROUTINE CONVECTIVE_ADJUSTMENT_INI
16 C | o Driver for vertical mixing or similar parameterization
17 C *==========================================================*
18 C | Same prognostic code logic as S/R CONVECTIVE_ADJUSTMENT,
19 C | but different time history behavior in forward-reverse
20 C | adjoint operation.
21 C *==========================================================*
22 C \ev
23
24 C !USES:
25 IMPLICIT NONE
26 C == Global data ==
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "DYNVARS.h"
31 #include "GRID.h"
32 #ifdef ALLOW_PASSIVE_TRACER
33 #include "TR1.h"
34 #endif
35 #ifdef ALLOW_TIMEAVE
36 #include "TIMEAVE_STATV.h"
37 #endif
38 #ifdef ALLOW_AUTODIFF_TAMC
39 #include "tamc.h"
40 #include "tamc_keys.h"
41 #endif /* ALLOW_AUTODIFF_TAMC */
42 EXTERNAL DIFFERENT_MULTIPLE
43 LOGICAL DIFFERENT_MULTIPLE
44
45 C !INPUT/OUTPUT PARAMETERS:
46 C == Routine arguments ==
47 C bi,bj,iMin,iMax,jMin,jMax,K - Loop counters
48 C myTime - Current time in simulation
49 C myIter - Current iteration in simulation
50 C myThid - Thread number of this instance of S/R CONVECT
51 INTEGER bi,bj,iMin,iMax,jMin,jMax
52 _RL myTime
53 INTEGER myIter
54 INTEGER myThid
55
56 #ifdef INCLUDE_CONVECT_CALL
57
58 C !LOCAL VARIABLES:
59 C == Local variables ==
60 C i,j,k :: Loop counters
61 C rhoKm1, rhoK :: Density at adjacent levels (ref. to same level)
62 C ConvectCount :: Convection freq. counter
63 INTEGER i, j, K, kTop, kBottom, kDir, deltaK
64 _RL rhoKm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65 _RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
66 _RL ConvectCount(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
67 _RL weightA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68 _RL weightB(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69 CEOP
70
71 C-- Check to see if should convect now
72 IF ( DIFFERENT_MULTIPLE(cAdjFreq,myTime,myTime-deltaTClock) ) THEN
73
74 C-- Initialise counters
75 kTop = 0
76 kBottom = 0
77 kDir = 0
78 deltaK = 0
79
80 C- Initialisation of Convection Counter
81 DO K=1,Nr
82 DO j=1-OLy,sNy+OLy
83 DO i=1-OLx,sNx+OLx
84 ConvectCount(i,j,k) = 0.
85 ENDDO
86 ENDDO
87 ENDDO
88
89 #ifdef ALLOW_AUTODIFF_TAMC
90 act1 = bi - myBxLo(myThid)
91 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
92 act2 = bj - myByLo(myThid)
93 max2 = myByHi(myThid) - myByLo(myThid) + 1
94 act3 = myThid - 1
95 max3 = nTx*nTy
96 act4 = 0
97 ikey = (act1 + 1) + act2*max1
98 & + act3*max1*max2
99 & + act4*max1*max2*max3
100 #endif /* ALLOW_AUTODIFF_TAMC */
101
102 IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
103 kTop = 2
104 kBottom = Nr
105 kDir = 1
106 deltaK = -1
107 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
108 kTop = Nr
109 kBottom = 2
110 kDir = -1
111 deltaK = 0
112 ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
113 kTop = Nr
114 kBottom = 2
115 kDir = -1
116 deltaK = 0
117 ELSE
118 STOP 'CONVECTIVE_ADJUSTMENT: We should never reach this point'
119 ENDIF
120
121 C-- Loop over all *interior* layers
122 DO K=kTop,kBottom,kDir
123
124 #ifdef ALLOW_AUTODIFF_TAMC
125 kkey = (ikey-1)*Nr + k
126 CADJ STORE theta(:,:,k-1,bi,bj) = tapelev_ini_bibj_k,
127 CADJ & key=kkey, byte=isbyte
128 CADJ STORE salt (:,:,k-1,bi,bj) = tapelev_ini_bibj_k,
129 CADJ & key=kkey, byte=isbyte
130 #endif /* ALLOW_AUTODIFF_TAMC */
131 C- Density of K-1 layer (above W(K)) reference to K-1 T-level
132 CALL FIND_RHO(
133 I bi,bj,iMin,iMax,jMin,jMax,K-1,K+deltaK,
134 I theta,salt,
135 O rhoKm1,
136 I myThid )
137
138 C- Density of K layer (below W(K)) reference to K-1 T-level.
139 #ifdef ALLOW_AUTODIFF_TAMC
140 CADJ STORE theta(:,:,k,bi,bj) = tapelev_ini_bibj_k,
141 CADJ & key = kkey, byte = isbyte
142 CADJ STORE salt (:,:,k,bi,bj) = tapelev_ini_bibj_k,
143 CADJ & key = kkey, byte = isbyte
144 #endif /* ALLOW_AUTODIFF_TAMC */
145 CALL FIND_RHO(
146 I bi,bj,iMin,iMax,jMin,jMax,K,K+deltaK,
147 I theta,salt,
148 O rhoK,
149 I myThid )
150
151 #ifdef ALLOW_AUTODIFF_TAMC
152 CADJ STORE rhoKm1(:,:) = tapelev_ini_bibj_k, key=kkey, byte=isbyte
153 CADJ STORE rhoK (:,:) = tapelev_ini_bibj_k, key=kkey, byte=isbyte
154 #endif /* ALLOW_AUTODIFF_TAMC */
155 C- Check static stability with layer below and mix as needed.
156 c CALL CONVECT(
157 c I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
158 c U ConvectCount,
159 c I myTime,myIter,myThid)
160
161 C- Pre-calculate mixing weights for interface K
162 CALL CONVECTIVE_WEIGHTS(
163 I bi,bj,K,rhoKm1,rhoK,
164 O weightA,weightB,ConvectCount,
165 I myThid)
166
167 C- Convectively mix heat across interface K
168 CALL CONVECTIVELY_MIXTRACER(
169 I bi,bj,k,weightA,weightB,
170 U theta,
171 I myThid)
172
173 C- Convectively mix salt across interface K
174 CALL CONVECTIVELY_MIXTRACER(
175 I bi,bj,k,weightA,weightB,
176 U salt,
177 I myThid)
178
179 #ifdef ALLOW_PASSIVE_TRACER
180 C- Convectively mix passive tracer across interface K
181 ceh3 needs an IF ( usePASSIVE_TRACER ) THEN
182 CALL CONVECTIVELY_MIXTRACER(
183 I bi,bj,k,weightA,weightB,
184 U Tr1,
185 I myThid)
186 #endif /* ALLOW_PASSIVE_TRACER */
187
188 #ifdef ALLOW_PTRACERS
189 C- Convectively mix passive tracers across interface K
190 IF ( usePTRACERS ) THEN
191 CALL PTRACERS_CONVECT(
192 I bi,bj,k,weightA,weightB,myThid)
193 ENDIF
194 #endif /* ALLOW_PTRACERS */
195
196 C-- End DO K=1,Nr
197 ENDDO
198
199 C-- End IF (DIFFERENT_MULTIPLE)
200 ENDIF
201
202 #endif /* INCLUDE_CONVECT_CALL */
203
204 RETURN
205 END

  ViewVC Help
Powered by ViewVC 1.1.22