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

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

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


Revision 1.10 - (hide annotations) (download)
Mon Nov 4 22:51:43 2002 UTC (21 years, 8 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint46n_post, checkpoint46m_post
Changes since 1.9: +30 -6 lines
o fixed convective_adjustment_ini.F: made the same changes as to convective_adjustment.F,
  that is, turned the k-loop upside down for p-coordinates.

1 mlosch 1.10 C $Header: /u/gcmpack/MITgcm/model/src/convective_adjustment_ini.F,v 1.9 2002/09/18 16:38:01 mlosch Exp $
2 cnh 1.3 C $Name: $
3 heimbach 1.1
4     #include "CPP_OPTIONS.h"
5    
6 cnh 1.3 CBOP
7     C !ROUTINE: CONVECTIVE_ADJUSTMENT_INI
8     C !INTERFACE:
9 heimbach 1.1 SUBROUTINE CONVECTIVE_ADJUSTMENT_INI(
10     I bi, bj, iMin, iMax, jMin, jMax,
11     I myTime, myIter, myThid )
12 cnh 1.3 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 heimbach 1.1 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 heimbach 1.6 #ifdef ALLOW_PASSIVE_TRACER
32     #include "TR1.h"
33     #endif
34 heimbach 1.1 #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 cnh 1.3 C !INPUT/OUTPUT PARAMETERS:
45 heimbach 1.1 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 cnh 1.3 C !LOCAL VARIABLES:
58 heimbach 1.1 C == Local variables ==
59 cnh 1.3 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 mlosch 1.10 INTEGER i, j, K, kTop, kBottom, kDir, kRef
63 heimbach 1.1 _RL rhoKm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64     _RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65 mlosch 1.10 _RL ConvectCount(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
66 adcroft 1.4 _RL weightA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67     _RL weightB(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68 cnh 1.3 CEOP
69 heimbach 1.1
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 heimbach 1.8 C-- CONVECT not needed with KPP mixing
97 heimbach 1.1 IF (
98 heimbach 1.8 & (.NOT.useKPP)
99 heimbach 1.1 & ) THEN
100     #endif /* ALLOW_KPP */
101    
102 mlosch 1.10 IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
103     kTop = 2
104     kBottom = Nr
105     kDir = 1
106     ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
107     kTop = Nr
108     kBottom = 2
109     kDir = -1
110     ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
111     kTop = Nr
112     kBottom = 2
113     kDir = -1
114     ELSE
115     STOP 'CONVECTIVE_ADJUSTMENT: We should never reach this point'
116     ENDIF
117    
118 heimbach 1.1 C-- Loop over all *interior* layers
119 mlosch 1.10 DO K=kTop,kBottom,kDir
120    
121     IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
122     kRef = k-1
123     ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
124     kRef = k
125     ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
126     kRef = k
127     ENDIF
128 heimbach 1.1
129     #ifdef ALLOW_AUTODIFF_TAMC
130 heimbach 1.2 kkey = (ikey-1)*Nr + k
131     CADJ STORE theta(:,:,k-1,bi,bj) = tapelev_ini_bibj_k,
132     CADJ & key=kkey, byte=isbyte
133     CADJ STORE salt (:,:,k-1,bi,bj) = tapelev_ini_bibj_k,
134     CADJ & key=kkey, byte=isbyte
135 heimbach 1.1 #endif /* ALLOW_AUTODIFF_TAMC */
136     C- Density of K-1 layer (above W(K)) reference to K-1 T-level
137     CALL FIND_RHO(
138 mlosch 1.10 I bi,bj,iMin,iMax,jMin,jMax,K-1,KRef,
139 heimbach 1.1 I theta,salt,
140     O rhoKm1,
141     I myThid )
142    
143     C- Density of K layer (below W(K)) reference to K-1 T-level.
144     #ifdef ALLOW_AUTODIFF_TAMC
145 heimbach 1.2 CADJ STORE theta(:,:,k,bi,bj) = tapelev_ini_bibj_k,
146     CADJ & key = kkey, byte = isbyte
147     CADJ STORE salt (:,:,k,bi,bj) = tapelev_ini_bibj_k,
148     CADJ & key = kkey, byte = isbyte
149 heimbach 1.1 #endif /* ALLOW_AUTODIFF_TAMC */
150     CALL FIND_RHO(
151 mlosch 1.10 I bi,bj,iMin,iMax,jMin,jMax,K,KRef,
152 heimbach 1.1 I theta,salt,
153     O rhoK,
154     I myThid )
155    
156     #ifdef ALLOW_AUTODIFF_TAMC
157 heimbach 1.2 CADJ STORE rhoKm1(:,:) = tapelev_ini_bibj_k, key=kkey, byte=isbyte
158     CADJ STORE rhoK (:,:) = tapelev_ini_bibj_k, key=kkey, byte=isbyte
159 heimbach 1.1 #endif /* ALLOW_AUTODIFF_TAMC */
160     C- Check static stability with layer below and mix as needed.
161 adcroft 1.4 c CALL CONVECT(
162     c I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
163     c U ConvectCount,
164     c I myTime,myIter,myThid)
165    
166     C- Pre-calculate mixing weights for interface K
167     CALL CONVECTIVE_WEIGHTS(
168     I bi,bj,K,rhoKm1,rhoK,
169     O weightA,weightB,ConvectCount,
170     I myThid)
171    
172     C- Convectively mix heat across interface K
173     CALL CONVECTIVELY_MIXTRACER(
174     I bi,bj,k,weightA,weightB,
175     U theta,
176     I myThid)
177    
178     C- Convectively mix salt across interface K
179     CALL CONVECTIVELY_MIXTRACER(
180     I bi,bj,k,weightA,weightB,
181     U salt,
182     I myThid)
183    
184     #ifdef ALLOW_PASSIVE_TRACER
185     C- Convectively mix passive tracer across interface K
186     CALL CONVECTIVELY_MIXTRACER(
187     I bi,bj,k,weightA,weightB,
188     U Tr1,
189     I myThid)
190     #endif /* ALLOW_PASSIVE_TRACER */
191 adcroft 1.5
192     #ifdef ALLOW_PTRACERS
193     C- Convectively mix passive tracers across interface K
194     IF ( usePTRACERS ) THEN
195     CALL PTRACERS_CONVECT(
196     I bi,bj,k,weightA,weightB,myThid)
197     ENDIF
198     #endif /* ALLOW_PTRACERS */
199 heimbach 1.1
200     C-- End DO K=1,Nr
201     ENDDO
202    
203     #ifdef ALLOW_TIMEAVE
204     IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
205     CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
206     I deltaTclock, bi, bj, myThid)
207     ENDIF
208     #endif /* ALLOW_TIMEAVE */
209    
210     #ifdef ALLOW_KPP
211     C-- End IF (.NOT.useKPP)
212     ENDIF
213     #endif /* ALLOW_KPP */
214    
215     C-- End IF (DIFFERENT_MULTIPLE)
216     ENDIF
217    
218     #endif /* INCLUDE_CONVECT_CALL */
219    
220     RETURN
221     END

  ViewVC Help
Powered by ViewVC 1.1.22