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

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

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


Revision 1.8 - (show annotations) (download)
Wed Sep 26 18:09:14 2001 UTC (22 years, 8 months ago) by cnh
Branch: MAIN
CVS Tags: release1_b1, checkpoint43, ecco-branch-mod1, release1_beta1, checkpoint42, checkpoint41
Branch point for: release1, ecco-branch, release1_coupled
Changes since 1.7: +18 -10 lines
Bringing comments up to data and formatting for document extraction.

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/convective_adjustment.F,v 1.7 2001/05/14 21:46:17 heimbach Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: CONVECTIVE_ADJUSTMENT
8 C !INTERFACE:
9 SUBROUTINE CONVECTIVE_ADJUSTMENT(
10 I bi, bj, iMin, iMax, jMin, jMax,
11 I myTime, myIter, myThid )
12 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 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 #ifdef ALLOW_TIMEAVE
28 #include "TIMEAVE_STATV.h"
29 #endif
30 #ifdef ALLOW_AUTODIFF_TAMC
31 #include "tamc.h"
32 #include "tamc_keys.h"
33 #endif /* ALLOW_AUTODIFF_TAMC */
34 EXTERNAL DIFFERENT_MULTIPLE
35 LOGICAL DIFFERENT_MULTIPLE
36
37 C !INPUT/OUTPUT PARAMETERS:
38 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 C !LOCAL VARIABLES:
51 C == Local variables ==
52 C rhoKm1, rhoK :: Density at adjacent levels (common ref. level)
53 C ConvectCount :: Convection mixing freq. counter.
54 INTEGER i, j, K
55 _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 CEOP
59
60 C-- Check to see if should convect now
61 IF ( DIFFERENT_MULTIPLE(cAdjFreq,myTime,myTime-deltaTClock) ) THEN
62
63 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 #ifdef ALLOW_AUTODIFF_TAMC
73 act1 = bi - myBxLo(myThid)
74 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
75
76 act2 = bj - myByLo(myThid)
77 max2 = myByHi(myThid) - myByLo(myThid) + 1
78
79 act3 = myThid - 1
80 max3 = nTx*nTy
81
82 act4 = ikey_dynamics - 1
83
84 ikey = (act1 + 1) + act2*max1
85 & + act3*max1*max2
86 & + act4*max1*max2*max3
87 #endif /* ALLOW_AUTODIFF_TAMC */
88
89 #ifdef ALLOW_KPP
90 IF (
91 & (.NOT.useKPP) ! CONVECT not needed with KPP mixing
92 & ) THEN
93 #endif /* ALLOW_KPP */
94
95 C-- Loop over all *interior* layers
96 DO K=2,Nr
97
98 #ifdef ALLOW_AUTODIFF_TAMC
99 kkey = (ikey-1)*Nr + k
100 CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
101 CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
102 #endif /* ALLOW_AUTODIFF_TAMC */
103 C- Density of K-1 layer (above W(K)) reference to K-1 T-level
104 CALL FIND_RHO(
105 I bi,bj,iMin,iMax,jMin,jMax,K-1,K-1,eosType,
106 I theta,salt,
107 O rhoKm1,
108 I myThid )
109
110 C- Density of K layer (below W(K)) reference to K-1 T-level.
111 #ifdef ALLOW_AUTODIFF_TAMC
112 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
113 CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
114 #endif /* ALLOW_AUTODIFF_TAMC */
115 CALL FIND_RHO(
116 I bi,bj,iMin,iMax,jMin,jMax,K,K-1,eosType,
117 I theta,salt,
118 O rhoK,
119 I myThid )
120
121 #ifdef ALLOW_AUTODIFF_TAMC
122 CADJ STORE rhoKm1(:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
123 CADJ STORE rhoK (:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
124 #endif /* ALLOW_AUTODIFF_TAMC */
125 C- Check static stability with layer below and mix as needed.
126 CALL CONVECT(
127 I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
128 U ConvectCount,
129 I myTime,myIter,myThid)
130
131 C-- End DO K=1,Nr
132 ENDDO
133
134 #ifdef ALLOW_TIMEAVE
135 IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
136 CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
137 I deltaTclock, bi, bj, myThid)
138 ENDIF
139 #endif /* ALLOW_TIMEAVE */
140
141 #ifdef ALLOW_KPP
142 C-- End IF (.NOT.useKPP)
143 ENDIF
144 #endif /* ALLOW_KPP */
145
146 C-- End IF (DIFFERENT_MULTIPLE)
147 ENDIF
148
149 #endif /* INCLUDE_CONVECT_CALL */
150
151 RETURN
152 END

  ViewVC Help
Powered by ViewVC 1.1.22