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

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

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


Revision 1.10 - (hide annotations) (download)
Tue Feb 26 19:50:12 2002 UTC (22 years, 4 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_pre
Changes since 1.9: +33 -5 lines
Re-wrote the convective mixing algorithm to use pre-calculated weights.

Uses two new routines:
 - convective_weights() calculates mixing factors A and B, called once
 - convectively_mixtracers() mixes a tracer (argument) using A and B
   and is called for each tracer

The old call to convect() is simply commented out for the time-being.
Similarly, convect.F still exists. I thought it prudent to leave them
around until the TAF/TAMC related bits are added.

1 adcroft 1.10 C $Header: /u/gcmpack/MITgcm/model/src/convective_adjustment.F,v 1.9 2002/01/11 17:31:19 heimbach Exp $
2 cnh 1.8 C $Name: $
3 adcroft 1.2
4     #include "CPP_OPTIONS.h"
5    
6 cnh 1.8 CBOP
7     C !ROUTINE: CONVECTIVE_ADJUSTMENT
8     C !INTERFACE:
9 adcroft 1.2 SUBROUTINE CONVECTIVE_ADJUSTMENT(
10     I bi, bj, iMin, iMax, jMin, jMax,
11     I myTime, myIter, myThid )
12 cnh 1.8 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 adcroft 1.2 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 jmc 1.5 #ifdef ALLOW_TIMEAVE
28     #include "TIMEAVE_STATV.h"
29 jmc 1.4 #endif
30 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
31     #include "tamc.h"
32     #include "tamc_keys.h"
33     #endif /* ALLOW_AUTODIFF_TAMC */
34 adcroft 1.2 EXTERNAL DIFFERENT_MULTIPLE
35     LOGICAL DIFFERENT_MULTIPLE
36    
37 cnh 1.8 C !INPUT/OUTPUT PARAMETERS:
38 adcroft 1.2 C == Routine arguments ==
39     C bi,bj,iMin,iMax,jMin,jMax,K - Loop counters
40     C myTime - Current time in simulation
41     C myIter - Current iteration in simulation
42     C myThid - Thread number of this instance of S/R CONVECT
43     INTEGER bi,bj,iMin,iMax,jMin,jMax
44     _RL myTime
45     INTEGER myIter
46     INTEGER myThid
47    
48     #ifdef INCLUDE_CONVECT_CALL
49    
50 cnh 1.8 C !LOCAL VARIABLES:
51 adcroft 1.2 C == Local variables ==
52 cnh 1.8 C rhoKm1, rhoK :: Density at adjacent levels (common ref. level)
53     C ConvectCount :: Convection mixing freq. counter.
54 jmc 1.4 INTEGER i, j, K
55 adcroft 1.2 _RL rhoKm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56     _RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57     _RL ConvectCount(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
58 adcroft 1.10 _RL weightA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59     _RL weightB(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60 cnh 1.8 CEOP
61 adcroft 1.2
62     C-- Check to see if should convect now
63     IF ( DIFFERENT_MULTIPLE(cAdjFreq,myTime,myTime-deltaTClock) ) THEN
64    
65 jmc 1.4 C- Initialisation of Convection Counter
66     DO K=1,Nr
67     DO j=1-OLy,sNy+OLy
68     DO i=1-OLx,sNx+OLx
69     ConvectCount(i,j,k) = 0.
70     ENDDO
71     ENDDO
72     ENDDO
73    
74 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
75     act1 = bi - myBxLo(myThid)
76     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
77     act2 = bj - myByLo(myThid)
78     max2 = myByHi(myThid) - myByLo(myThid) + 1
79     act3 = myThid - 1
80     max3 = nTx*nTy
81     act4 = ikey_dynamics - 1
82     ikey = (act1 + 1) + act2*max1
83     & + act3*max1*max2
84     & + act4*max1*max2*max3
85     #endif /* ALLOW_AUTODIFF_TAMC */
86    
87 adcroft 1.2 #ifdef ALLOW_KPP
88     IF (
89     & (.NOT.useKPP) ! CONVECT not needed with KPP mixing
90     & ) THEN
91     #endif /* ALLOW_KPP */
92    
93     C-- Loop over all *interior* layers
94     DO K=2,Nr
95    
96     #ifdef ALLOW_AUTODIFF_TAMC
97 heimbach 1.7 kkey = (ikey-1)*Nr + k
98     CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
99     CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
100 adcroft 1.2 #endif /* ALLOW_AUTODIFF_TAMC */
101     C- Density of K-1 layer (above W(K)) reference to K-1 T-level
102     CALL FIND_RHO(
103     I bi,bj,iMin,iMax,jMin,jMax,K-1,K-1,eosType,
104     I theta,salt,
105     O rhoKm1,
106     I myThid )
107    
108     C- Density of K layer (below W(K)) reference to K-1 T-level.
109     #ifdef ALLOW_AUTODIFF_TAMC
110 heimbach 1.7 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
111     CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
112 adcroft 1.2 #endif /* ALLOW_AUTODIFF_TAMC */
113     CALL FIND_RHO(
114     I bi,bj,iMin,iMax,jMin,jMax,K,K-1,eosType,
115     I theta,salt,
116     O rhoK,
117     I myThid )
118    
119     #ifdef ALLOW_AUTODIFF_TAMC
120 heimbach 1.7 CADJ STORE rhoKm1(:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
121     CADJ STORE rhoK (:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
122 adcroft 1.2 #endif /* ALLOW_AUTODIFF_TAMC */
123     C- Check static stability with layer below and mix as needed.
124 adcroft 1.10 c CALL CONVECT(
125     c I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
126     c U ConvectCount,
127     c I myTime,myIter,myThid)
128    
129     C- Pre-calculate mixing weights for interface K
130     CALL CONVECTIVE_WEIGHTS(
131     I bi,bj,K,rhoKm1,rhoK,
132     O weightA,weightB,ConvectCount,
133     I myThid)
134    
135     C- Convectively mix heat across interface K
136     CALL CONVECTIVELY_MIXTRACER(
137     I bi,bj,k,weightA,weightB,
138     U theta,
139     I myThid)
140    
141     C- Convectively mix salt across interface K
142     CALL CONVECTIVELY_MIXTRACER(
143     I bi,bj,k,weightA,weightB,
144     U salt,
145     I myThid)
146    
147     #ifdef ALLOW_PASSIVE_TRACER
148     C- Convectively mix passive tracer across interface K
149     CALL CONVECTIVELY_MIXTRACER(
150     I bi,bj,k,weightA,weightB,
151     U Tr1,
152     I myThid)
153     #endif /* ALLOW_PASSIVE_TRACER */
154 jmc 1.4
155 adcroft 1.2 C-- End DO K=1,Nr
156     ENDDO
157    
158 jmc 1.5 #ifdef ALLOW_TIMEAVE
159     IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
160     CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
161     I deltaTclock, bi, bj, myThid)
162     ENDIF
163     #endif /* ALLOW_TIMEAVE */
164    
165 adcroft 1.2 #ifdef ALLOW_KPP
166     C-- End IF (.NOT.useKPP)
167     ENDIF
168     #endif /* ALLOW_KPP */
169    
170     C-- End IF (DIFFERENT_MULTIPLE)
171     ENDIF
172    
173     #endif /* INCLUDE_CONVECT_CALL */
174    
175     RETURN
176     END

  ViewVC Help
Powered by ViewVC 1.1.22