/[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.13 - (show annotations) (download)
Thu May 30 22:48:33 2002 UTC (22 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46g_pre, checkpoint46f_post, checkpoint46b_post, checkpoint46d_pre, checkpoint45d_post, checkpoint46a_post, checkpoint46e_pre, checkpoint46b_pre, checkpoint46c_pre, checkpoint46, checkpoint46a_pre, checkpoint45c_post, checkpoint46c_post, checkpoint46e_post, checkpoint46d_post
Changes since 1.12: +3 -2 lines
removed some f90 comments ("!")

1 C $Header: /u/gcmpack/MITgcm/model/src/convective_adjustment.F,v 1.12 2002/03/24 02:08:21 heimbach 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
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- Initialisation of Convection Counter
69 DO K=1,Nr
70 DO j=1-OLy,sNy+OLy
71 DO i=1-OLx,sNx+OLx
72 ConvectCount(i,j,k) = 0.
73 ENDDO
74 ENDDO
75 ENDDO
76
77 #ifdef ALLOW_AUTODIFF_TAMC
78 act1 = bi - myBxLo(myThid)
79 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
80 act2 = bj - myByLo(myThid)
81 max2 = myByHi(myThid) - myByLo(myThid) + 1
82 act3 = myThid - 1
83 max3 = nTx*nTy
84 act4 = ikey_dynamics - 1
85 ikey = (act1 + 1) + act2*max1
86 & + act3*max1*max2
87 & + act4*max1*max2*max3
88 #endif /* ALLOW_AUTODIFF_TAMC */
89
90 #ifdef ALLOW_KPP
91 C-- CONVECT not needed with KPP mixing
92 IF (
93 & (.NOT.useKPP)
94 & ) THEN
95 #endif /* ALLOW_KPP */
96
97 C-- Loop over all *interior* layers
98 DO K=2,Nr
99
100 #ifdef ALLOW_AUTODIFF_TAMC
101 kkey = (ikey-1)*Nr + k
102 CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
103 CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
104 #endif /* ALLOW_AUTODIFF_TAMC */
105 C- Density of K-1 layer (above W(K)) reference to K-1 T-level
106 CALL FIND_RHO(
107 I bi,bj,iMin,iMax,jMin,jMax,K-1,K-1,eosType,
108 I theta,salt,
109 O rhoKm1,
110 I myThid )
111
112 C- Density of K layer (below W(K)) reference to K-1 T-level.
113 #ifdef ALLOW_AUTODIFF_TAMC
114 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
115 CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
116 #endif /* ALLOW_AUTODIFF_TAMC */
117 CALL FIND_RHO(
118 I bi,bj,iMin,iMax,jMin,jMax,K,K-1,eosType,
119 I theta,salt,
120 O rhoK,
121 I myThid )
122
123 #ifdef ALLOW_AUTODIFF_TAMC
124 CADJ STORE rhoKm1(:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
125 CADJ STORE rhoK (:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
126 #endif /* ALLOW_AUTODIFF_TAMC */
127 C- Check static stability with layer below and mix as needed.
128 c CALL CONVECT(
129 c I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
130 c U ConvectCount,
131 c I myTime,myIter,myThid)
132
133 C- Pre-calculate mixing weights for interface K
134 CALL CONVECTIVE_WEIGHTS(
135 I bi,bj,K,rhoKm1,rhoK,
136 O weightA,weightB,ConvectCount,
137 I myThid)
138
139 C- Convectively mix heat across interface K
140 CALL CONVECTIVELY_MIXTRACER(
141 I bi,bj,k,weightA,weightB,
142 U theta,
143 I myThid)
144
145 C- Convectively mix salt across interface K
146 CALL CONVECTIVELY_MIXTRACER(
147 I bi,bj,k,weightA,weightB,
148 U salt,
149 I myThid)
150
151 #ifdef ALLOW_PASSIVE_TRACER
152 C- Convectively mix passive tracer across interface K
153 CALL CONVECTIVELY_MIXTRACER(
154 I bi,bj,k,weightA,weightB,
155 U Tr1,
156 I myThid)
157 #endif /* ALLOW_PASSIVE_TRACER */
158
159 #ifdef ALLOW_PTRACERS
160 C- Convectively mix passive tracers across interface K
161 IF ( usePTRACERS ) THEN
162 CALL PTRACERS_CONVECT(
163 I bi,bj,k,weightA,weightB,myThid)
164 ENDIF
165 #endif /* ALLOW_PTRACERS */
166
167 C-- End DO K=1,Nr
168 ENDDO
169
170 #ifdef ALLOW_TIMEAVE
171 IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
172 CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
173 I deltaTclock, bi, bj, myThid)
174 ENDIF
175 #endif /* ALLOW_TIMEAVE */
176
177 #ifdef ALLOW_KPP
178 C-- End IF (.NOT.useKPP)
179 ENDIF
180 #endif /* ALLOW_KPP */
181
182 C-- End IF (DIFFERENT_MULTIPLE)
183 ENDIF
184
185 #endif /* INCLUDE_CONVECT_CALL */
186
187 RETURN
188 END

  ViewVC Help
Powered by ViewVC 1.1.22