/[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.5 - (hide annotations) (download)
Tue Mar 6 17:19:25 2001 UTC (23 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: pre38tag1, pre38-close, checkpoint37
Branch point for: pre38
Changes since 1.4: +11 -11 lines
change Time-Average routine names (new package)

1 jmc 1.5 C $Header: /u/gcmpack/models/MITgcmUV/model/src/convective_adjustment.F,v 1.4 2001/02/14 22:51:27 jmc Exp $
2     C $Name: $
3 adcroft 1.2
4     #include "CPP_OPTIONS.h"
5    
6     SUBROUTINE CONVECTIVE_ADJUSTMENT(
7     I bi, bj, iMin, iMax, jMin, jMax,
8     I myTime, myIter, myThid )
9     C /==========================================================\
10     C | SUBROUTINE CONVECTIVE_ADJUSTMENT |
11     C | o Calls vertical mixing or similar parameterization |
12     C \==========================================================/
13     IMPLICIT NONE
14    
15     C == Global data ==
16     #include "SIZE.h"
17     #include "EEPARAMS.h"
18     #include "PARAMS.h"
19     #include "DYNVARS.h"
20     #include "GRID.h"
21    
22 jmc 1.5 #ifdef ALLOW_TIMEAVE
23     #include "TIMEAVE_STATV.h"
24 jmc 1.4 #endif
25    
26 adcroft 1.2 EXTERNAL DIFFERENT_MULTIPLE
27     LOGICAL DIFFERENT_MULTIPLE
28    
29     C == Routine arguments ==
30     C bi,bj,iMin,iMax,jMin,jMax,K - Loop counters
31     C myTime - Current time in simulation
32     C myIter - Current iteration in simulation
33     C myThid - Thread number of this instance of S/R CONVECT
34     INTEGER bi,bj,iMin,iMax,jMin,jMax
35     _RL myTime
36     INTEGER myIter
37     INTEGER myThid
38    
39     #ifdef INCLUDE_CONVECT_CALL
40    
41     C == Local variables ==
42 jmc 1.4 INTEGER i, j, K
43 adcroft 1.2 _RL rhoKm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44     _RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45     _RL ConvectCount(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
46    
47     C-- Check to see if should convect now
48     IF ( DIFFERENT_MULTIPLE(cAdjFreq,myTime,myTime-deltaTClock) ) THEN
49    
50 jmc 1.4 C- Initialisation of Convection Counter
51     DO K=1,Nr
52     DO j=1-OLy,sNy+OLy
53     DO i=1-OLx,sNx+OLx
54     ConvectCount(i,j,k) = 0.
55     ENDDO
56     ENDDO
57     ENDDO
58    
59 adcroft 1.2 #ifdef ALLOW_KPP
60     IF (
61     & (.NOT.useKPP) ! CONVECT not needed with KPP mixing
62     & ) THEN
63     #endif /* ALLOW_KPP */
64    
65     C-- Loop over all *interior* layers
66     DO K=2,Nr
67    
68     #ifdef ALLOW_AUTODIFF_TAMC
69     CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
70     CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
71     #endif /* ALLOW_AUTODIFF_TAMC */
72     C- Density of K-1 layer (above W(K)) reference to K-1 T-level
73     CALL FIND_RHO(
74     I bi,bj,iMin,iMax,jMin,jMax,K-1,K-1,eosType,
75     I theta,salt,
76     O rhoKm1,
77     I myThid )
78    
79     C- Density of K layer (below W(K)) reference to K-1 T-level.
80     #ifdef ALLOW_AUTODIFF_TAMC
81     CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
82     CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj, key = ikey, byte = isbyte
83     #endif /* ALLOW_AUTODIFF_TAMC */
84     CALL FIND_RHO(
85     I bi,bj,iMin,iMax,jMin,jMax,K,K-1,eosType,
86     I theta,salt,
87     O rhoK,
88     I myThid )
89    
90     #ifdef ALLOW_AUTODIFF_TAMC
91     CADJ STORE rhoKm1(:,:) = comlev1_bibj, key = ikey, byte = isbyte
92     CADJ STORE rhoKp1(:,:) = comlev1_bibj, key = ikey, byte = isbyte
93     #endif /* ALLOW_AUTODIFF_TAMC */
94     C- Check static stability with layer below and mix as needed.
95     CALL CONVECT(
96     I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
97     U ConvectCount,
98     I myTime,myIter,myThid)
99 jmc 1.4
100 adcroft 1.2 C-- End DO K=1,Nr
101     ENDDO
102    
103 jmc 1.5 #ifdef ALLOW_TIMEAVE
104     IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
105     CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
106     I deltaTclock, bi, bj, myThid)
107     ENDIF
108     #endif /* ALLOW_TIMEAVE */
109    
110 adcroft 1.2 #ifdef ALLOW_KPP
111     C-- End IF (.NOT.useKPP)
112     ENDIF
113     #endif /* ALLOW_KPP */
114    
115     C-- End IF (DIFFERENT_MULTIPLE)
116     ENDIF
117    
118     #endif /* INCLUDE_CONVECT_CALL */
119    
120     RETURN
121     END

  ViewVC Help
Powered by ViewVC 1.1.22