/[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.7 - (show annotations) (download)
Mon May 14 21:46:17 2001 UTC (23 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint40pre3, checkpoint40pre1, checkpoint40pre7, checkpoint40pre6, checkpoint40pre9, checkpoint40pre8, checkpoint40pre2, checkpoint40pre4, checkpoint39, checkpoint40pre5, checkpoint40
Changes since 1.6: +9 -8 lines
Modifications/fixes to support TAMC differentiability
(mostly missing or wrong directives).

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/convective_adjustment.F,v 1.6 2001/03/25 22:33:52 heimbach Exp $
2 C $Name: checkpoint38 $
3
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 #ifdef ALLOW_TIMEAVE
23 #include "TIMEAVE_STATV.h"
24 #endif
25
26 #ifdef ALLOW_AUTODIFF_TAMC
27 #include "tamc.h"
28 #include "tamc_keys.h"
29 #endif /* ALLOW_AUTODIFF_TAMC */
30
31 EXTERNAL DIFFERENT_MULTIPLE
32 LOGICAL DIFFERENT_MULTIPLE
33
34 C == Routine arguments ==
35 C bi,bj,iMin,iMax,jMin,jMax,K - Loop counters
36 C myTime - Current time in simulation
37 C myIter - Current iteration in simulation
38 C myThid - Thread number of this instance of S/R CONVECT
39 INTEGER bi,bj,iMin,iMax,jMin,jMax
40 _RL myTime
41 INTEGER myIter
42 INTEGER myThid
43
44 #ifdef INCLUDE_CONVECT_CALL
45
46 C == Local variables ==
47 INTEGER i, j, K
48 _RL rhoKm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
49 _RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50 _RL ConvectCount(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
51
52 C-- Check to see if should convect now
53 IF ( DIFFERENT_MULTIPLE(cAdjFreq,myTime,myTime-deltaTClock) ) THEN
54
55 C- Initialisation of Convection Counter
56 DO K=1,Nr
57 DO j=1-OLy,sNy+OLy
58 DO i=1-OLx,sNx+OLx
59 ConvectCount(i,j,k) = 0.
60 ENDDO
61 ENDDO
62 ENDDO
63
64 #ifdef ALLOW_AUTODIFF_TAMC
65 act1 = bi - myBxLo(myThid)
66 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
67
68 act2 = bj - myByLo(myThid)
69 max2 = myByHi(myThid) - myByLo(myThid) + 1
70
71 act3 = myThid - 1
72 max3 = nTx*nTy
73
74 act4 = ikey_dynamics - 1
75
76 ikey = (act1 + 1) + act2*max1
77 & + act3*max1*max2
78 & + act4*max1*max2*max3
79 #endif /* ALLOW_AUTODIFF_TAMC */
80
81 #ifdef ALLOW_KPP
82 IF (
83 & (.NOT.useKPP) ! CONVECT not needed with KPP mixing
84 & ) THEN
85 #endif /* ALLOW_KPP */
86
87 C-- Loop over all *interior* layers
88 DO K=2,Nr
89
90 #ifdef ALLOW_AUTODIFF_TAMC
91 kkey = (ikey-1)*Nr + k
92 CADJ STORE theta(:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
93 CADJ STORE salt (:,:,k-1,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
94 #endif /* ALLOW_AUTODIFF_TAMC */
95 C- Density of K-1 layer (above W(K)) reference to K-1 T-level
96 CALL FIND_RHO(
97 I bi,bj,iMin,iMax,jMin,jMax,K-1,K-1,eosType,
98 I theta,salt,
99 O rhoKm1,
100 I myThid )
101
102 C- Density of K layer (below W(K)) reference to K-1 T-level.
103 #ifdef ALLOW_AUTODIFF_TAMC
104 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
105 CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
106 #endif /* ALLOW_AUTODIFF_TAMC */
107 CALL FIND_RHO(
108 I bi,bj,iMin,iMax,jMin,jMax,K,K-1,eosType,
109 I theta,salt,
110 O rhoK,
111 I myThid )
112
113 #ifdef ALLOW_AUTODIFF_TAMC
114 CADJ STORE rhoKm1(:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
115 CADJ STORE rhoK (:,:) = comlev1_bibj_k, key = kkey, byte = isbyte
116 #endif /* ALLOW_AUTODIFF_TAMC */
117 C- Check static stability with layer below and mix as needed.
118 CALL CONVECT(
119 I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
120 U ConvectCount,
121 I myTime,myIter,myThid)
122
123 C-- End DO K=1,Nr
124 ENDDO
125
126 #ifdef ALLOW_TIMEAVE
127 IF (myIter.ne.nIter0 .AND. taveFreq.GT.0.) THEN
128 CALL TIMEAVE_CUMULATE(ConvectCountTave, ConvectCount, Nr,
129 I deltaTclock, bi, bj, myThid)
130 ENDIF
131 #endif /* ALLOW_TIMEAVE */
132
133 #ifdef ALLOW_KPP
134 C-- End IF (.NOT.useKPP)
135 ENDIF
136 #endif /* ALLOW_KPP */
137
138 C-- End IF (DIFFERENT_MULTIPLE)
139 ENDIF
140
141 #endif /* INCLUDE_CONVECT_CALL */
142
143 RETURN
144 END

  ViewVC Help
Powered by ViewVC 1.1.22