/[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.22 - (show annotations) (download)
Fri Sep 17 22:57:11 2004 UTC (19 years, 9 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint55, checkpoint55c_post, checkpoint55g_post, checkpoint55d_post, checkpoint55d_pre, checkpoint55b_post, checkpoint55f_post, checkpoint55a_post, checkpoint55e_post
Changes since 1.21: +1 -13 lines
o remove all tr1-related code (ALLOW_PASSIVE_TRACER)
  (adjoint stuff still has some tr1 names, but all use ptracer arrays)

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

  ViewVC Help
Powered by ViewVC 1.1.22