/[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.8 - (show annotations) (download)
Thu May 30 22:48:33 2002 UTC (22 years, 1 month 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.7: +3 -2 lines
removed some f90 comments ("!")

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

  ViewVC Help
Powered by ViewVC 1.1.22