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

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

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


Revision 1.17 - (show annotations) (download)
Fri Nov 15 03:01:21 2002 UTC (21 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint47e_post, checkpoint47c_post, checkpoint48e_post, checkpoint50c_pre, checkpoint48i_post, checkpoint50, checkpoint50b_pre, checkpoint48b_post, checkpoint48c_pre, checkpoint47d_pre, checkpoint47a_post, checkpoint48d_pre, checkpoint47i_post, checkpoint47d_post, checkpoint48d_post, checkpoint48f_post, checkpoint48h_post, checkpoint47g_post, checkpoint48a_post, checkpoint50a_post, checkpoint47j_post, branch-exfmods-tag, checkpoint48c_post, checkpoint47b_post, checkpoint47f_post, checkpoint47, checkpoint48, checkpoint49, checkpoint48g_post, checkpoint47h_post, checkpoint50b_post
Branch point for: branch-exfmods-curt
Changes since 1.16: +15 -14 lines
differentiable version of checkpoint46n_post
o external_fields_load now part of differentiation list
o pressure needs multiple storing;
  would be nice to have store_pressure at beginning or
  end of forward_step, e.g. by having phiHyd global (5-dim.)
  (NB: pressure is needed for certain cases in find_rho,
  which is also invoked through convective_adjustment).
o recomputations in find_rho for cases
 'JMD95'/'UNESCO' or 'MDJWF' are OK.
o #define ATMOSPHERIC_LOADING should be differentiable
o ini_forcing shifted to begining of initialise_varia

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

  ViewVC Help
Powered by ViewVC 1.1.22