/[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.9 - (hide annotations) (download)
Fri Jan 11 17:31:19 2002 UTC (22 years, 4 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint43a-release1mods, chkpt44d_post, checkpoint44e_pre, release1-branch_tutorials, chkpt44a_post, chkpt44c_pre, release1-branch-end, checkpoint44b_post, chkpt44a_pre, checkpoint44b_pre, checkpoint44, chkpt44c_post, release1-branch_branchpoint
Branch point for: release1_final, release1-branch
Changes since 1.8: +1 -5 lines
Minor cleanup.

1 heimbach 1.9 C $Header: /u/gcmpack/MITgcm/model/src/convective_adjustment.F,v 1.8 2001/09/26 18:09:14 cnh 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 cnh 1.8 CEOP
59 adcroft 1.2
60     C-- Check to see if should convect now
61     IF ( DIFFERENT_MULTIPLE(cAdjFreq,myTime,myTime-deltaTClock) ) THEN
62    
63 jmc 1.4 C- Initialisation of Convection Counter
64     DO K=1,Nr
65     DO j=1-OLy,sNy+OLy
66     DO i=1-OLx,sNx+OLx
67     ConvectCount(i,j,k) = 0.
68     ENDDO
69     ENDDO
70     ENDDO
71    
72 heimbach 1.6 #ifdef ALLOW_AUTODIFF_TAMC
73     act1 = bi - myBxLo(myThid)
74     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
75     act2 = bj - myByLo(myThid)
76     max2 = myByHi(myThid) - myByLo(myThid) + 1
77     act3 = myThid - 1
78     max3 = nTx*nTy
79     act4 = ikey_dynamics - 1
80     ikey = (act1 + 1) + act2*max1
81     & + act3*max1*max2
82     & + act4*max1*max2*max3
83     #endif /* ALLOW_AUTODIFF_TAMC */
84    
85 adcroft 1.2 #ifdef ALLOW_KPP
86     IF (
87     & (.NOT.useKPP) ! CONVECT not needed with KPP mixing
88     & ) THEN
89     #endif /* ALLOW_KPP */
90    
91     C-- Loop over all *interior* layers
92     DO K=2,Nr
93    
94     #ifdef ALLOW_AUTODIFF_TAMC
95 heimbach 1.7 kkey = (ikey-1)*Nr + k
96     CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
97     CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
98 adcroft 1.2 #endif /* ALLOW_AUTODIFF_TAMC */
99     C- Density of K-1 layer (above W(K)) reference to K-1 T-level
100     CALL FIND_RHO(
101     I bi,bj,iMin,iMax,jMin,jMax,K-1,K-1,eosType,
102     I theta,salt,
103     O rhoKm1,
104     I myThid )
105    
106     C- Density of K layer (below W(K)) reference to K-1 T-level.
107     #ifdef ALLOW_AUTODIFF_TAMC
108 heimbach 1.7 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
109     CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
110 adcroft 1.2 #endif /* ALLOW_AUTODIFF_TAMC */
111     CALL FIND_RHO(
112     I bi,bj,iMin,iMax,jMin,jMax,K,K-1,eosType,
113     I theta,salt,
114     O rhoK,
115     I myThid )
116    
117     #ifdef ALLOW_AUTODIFF_TAMC
118 heimbach 1.7 CADJ STORE rhoKm1(:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
119     CADJ STORE rhoK (:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
120 adcroft 1.2 #endif /* ALLOW_AUTODIFF_TAMC */
121     C- Check static stability with layer below and mix as needed.
122     CALL CONVECT(
123     I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
124     U ConvectCount,
125     I myTime,myIter,myThid)
126 jmc 1.4
127 adcroft 1.2 C-- End DO K=1,Nr
128     ENDDO
129    
130 jmc 1.5 #ifdef ALLOW_TIMEAVE
131     IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
132     CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
133     I deltaTclock, bi, bj, myThid)
134     ENDIF
135     #endif /* ALLOW_TIMEAVE */
136    
137 adcroft 1.2 #ifdef ALLOW_KPP
138     C-- End IF (.NOT.useKPP)
139     ENDIF
140     #endif /* ALLOW_KPP */
141    
142     C-- End IF (DIFFERENT_MULTIPLE)
143     ENDIF
144    
145     #endif /* INCLUDE_CONVECT_CALL */
146    
147     RETURN
148     END

  ViewVC Help
Powered by ViewVC 1.1.22