/[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.15 - (show annotations) (download)
Fri Nov 1 22:00:33 2002 UTC (21 years, 7 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint46l_post
Changes since 1.14: +29 -5 lines
 made convective adjustment work with pressure coordinates:
 - changed the direction of k-loop in convective_adjustment.F for the
   case of pressure coordinates (OCEANICP,ATMOSPHERIC buoyancyRelation)
 - adjusted the reference pressure k-index in convective_adjustment.F
 - adjusted the convection condition in convect.F (in analogy to
   calc_ivdc.F)
 - convective_adjustment no longer computes anything on the halos
 - removed the warnings about negative salinity from find_rho.F and
   find_alpha.F; instead the new routine look_for_neg_salinity, called
   at the beginning of find_rho, find_alpha, and find_beta, does a
   check of the entire slice, if CPP-option
   CHECK_SALINITY_FOR_NEGATIVE_VALUES is defined

1 C $Header: /u/gcmpack/MITgcm/model/src/convective_adjustment.F,v 1.14 2002/09/18 16:38:01 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, kRef
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 IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
98 kTop = 2
99 kBottom = Nr
100 kDir = 1
101 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
102 kTop = Nr-1
103 kBottom = 1
104 kDir = -1
105 ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
106 kTop = Nr-1
107 kBottom = 1
108 kDir = -1
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 IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
117 kRef = k-1
118 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
119 kRef = k
120 ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
121 kRef = k
122 ENDIF
123
124 #ifdef ALLOW_AUTODIFF_TAMC
125 kkey = (ikey-1)*Nr + k
126 CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
127 CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
128 #endif /* ALLOW_AUTODIFF_TAMC */
129 C- Density of K-1 layer (above W(K)) reference to K-1 T-level
130 CALL FIND_RHO(
131 I bi,bj,iMin,iMax,jMin,jMax,K-1,KRef,
132 I theta,salt,
133 O rhoKm1,
134 I myThid )
135
136 C- Density of K layer (below W(K)) reference to K-1 T-level.
137 #ifdef ALLOW_AUTODIFF_TAMC
138 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
139 CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
140 #endif /* ALLOW_AUTODIFF_TAMC */
141 CALL FIND_RHO(
142 I bi,bj,iMin,iMax,jMin,jMax,K,KRef,
143 I theta,salt,
144 O rhoK,
145 I myThid )
146
147 #ifdef ALLOW_AUTODIFF_TAMC
148 CADJ STORE rhoKm1(:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
149 CADJ STORE rhoK (:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
150 #endif /* ALLOW_AUTODIFF_TAMC */
151 C- Check static stability with layer below and mix as needed.
152 c CALL CONVECT(
153 c I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
154 c U ConvectCount,
155 c I myTime,myIter,myThid)
156
157 C- Pre-calculate mixing weights for interface K
158 CALL CONVECTIVE_WEIGHTS(
159 I bi,bj,K,rhoKm1,rhoK,
160 O weightA,weightB,ConvectCount,
161 I myThid)
162
163 C- Convectively mix heat across interface K
164 CALL CONVECTIVELY_MIXTRACER(
165 I bi,bj,k,weightA,weightB,
166 U theta,
167 I myThid)
168
169 C- Convectively mix salt across interface K
170 CALL CONVECTIVELY_MIXTRACER(
171 I bi,bj,k,weightA,weightB,
172 U salt,
173 I myThid)
174
175 #ifdef ALLOW_PASSIVE_TRACER
176 C- Convectively mix passive tracer across interface K
177 CALL CONVECTIVELY_MIXTRACER(
178 I bi,bj,k,weightA,weightB,
179 U Tr1,
180 I myThid)
181 #endif /* ALLOW_PASSIVE_TRACER */
182
183 #ifdef ALLOW_PTRACERS
184 C- Convectively mix passive tracers across interface K
185 IF ( usePTRACERS ) THEN
186 CALL PTRACERS_CONVECT(
187 I bi,bj,k,weightA,weightB,myThid)
188 ENDIF
189 #endif /* ALLOW_PTRACERS */
190
191 C-- End DO K=1,Nr
192 ENDDO
193
194 #ifdef ALLOW_TIMEAVE
195 IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
196 CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
197 I deltaTclock, bi, bj, myThid)
198 ENDIF
199 #endif /* ALLOW_TIMEAVE */
200
201 #ifdef ALLOW_KPP
202 C-- End IF (.NOT.useKPP)
203 ENDIF
204 #endif /* ALLOW_KPP */
205
206 C-- End IF (DIFFERENT_MULTIPLE)
207 ENDIF
208
209 #endif /* INCLUDE_CONVECT_CALL */
210
211 RETURN
212 END

  ViewVC Help
Powered by ViewVC 1.1.22