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

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

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


Revision 1.23 - (show annotations) (download)
Fri Apr 4 20:54:11 2014 UTC (10 years, 2 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64w, checkpoint64v, HEAD
Changes since 1.22: +14 -9 lines
- Start to include explicitly AUTODIFF_OPTIONS.h, COST_OPTIONS.h,
  and CTRL_OPTIONS.h in src files (to enable to skip the ECCO_CPPOPTIONS.h)
  For now, only in pkgs used in verification/hs94.1x64x5.
- Replace ALLOW_AUTODIFF_TAMC by ALLOW_AUTODIFF (except for tape/storage
  which are specific to TAF/TAMC).

1 C $Header: /u/gcmpack/MITgcm/model/src/convective_adjustment_ini.F,v 1.22 2008/08/11 22:25:52 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6 #ifdef ALLOW_AUTODIFF
7 # include "AUTODIFF_OPTIONS.h"
8 #endif
9
10 CBOP
11 C !ROUTINE: CONVECTIVE_ADJUSTMENT_INI
12 C !INTERFACE:
13 SUBROUTINE CONVECTIVE_ADJUSTMENT_INI(
14 I bi, bj, myTime, myIter, myThid )
15 C !DESCRIPTION: \bv
16 C *==========================================================*
17 C | SUBROUTINE CONVECTIVE_ADJUSTMENT_INI
18 C | o Driver for vertical mixing or similar parameterization
19 C *==========================================================*
20 C | Same prognostic code logic as S/R CONVECTIVE_ADJUSTMENT,
21 C | but different time history behavior in forward-reverse
22 C | adjoint operation.
23 C *==========================================================*
24 C \ev
25
26 C !USES:
27 IMPLICIT NONE
28 C == Global data ==
29 #include "SIZE.h"
30 #include "EEPARAMS.h"
31 #include "PARAMS.h"
32 #include "DYNVARS.h"
33 #include "GRID.h"
34 #ifdef ALLOW_TIMEAVE
35 #include "TIMEAVE_STATV.h"
36 #endif
37 #ifdef ALLOW_AUTODIFF
38 #include "tamc.h"
39 #include "tamc_keys.h"
40 #endif /* ALLOW_AUTODIFF */
41
42 C !INPUT/OUTPUT PARAMETERS:
43 C == Routine arguments ==
44 C bi,bj :: tile indices
45 C myTime :: Current time in simulation
46 C myIter :: Current iteration in simulation
47 C myThid :: Thread number of this instance of S/R CONVECT
48 INTEGER bi,bj
49 _RL myTime
50 INTEGER myIter
51 INTEGER myThid
52
53 #ifdef INCLUDE_CONVECT_CALL
54
55 C !FUNCTIONS:
56 EXTERNAL DIFFERENT_MULTIPLE
57 LOGICAL DIFFERENT_MULTIPLE
58
59 C !LOCAL VARIABLES:
60 C == Local variables ==
61 C iMin,iMax,jMin,jMax :: computation domain
62 C i,j,k :: Loop counters
63 C rhoKm1, rhoK :: Density at adjacent levels (ref. to same level)
64 C ConvectCount :: Convection freq. counter
65 INTEGER iMin,iMax,jMin,jMax
66 INTEGER i, j, K, kTop, kBottom, kDir, deltaK
67 _RL rhoKm1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68 _RL rhoK (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
69 _RL ConvectCount(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
70 _RL weightA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 _RL weightB(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
72 CEOP
73
74 C-- Check to see if should convect now
75 IF ( DIFFERENT_MULTIPLE(cAdjFreq,myTime,deltaTClock)
76 & ) THEN
77
78 C-- Define computation domain
79 iMin=1-OLx
80 iMax=sNx+OLx
81 jMin=1-OLy
82 jMax=sNy+OLy
83
84 C-- Initialise counters
85 kTop = 0
86 kBottom = 0
87 kDir = 0
88 deltaK = 0
89
90 C- Initialisation of Convection Counter
91 DO K=1,Nr
92 DO j=1-OLy,sNy+OLy
93 DO i=1-OLx,sNx+OLx
94 ConvectCount(i,j,k) = 0.
95 ENDDO
96 ENDDO
97 ENDDO
98
99 #ifdef ALLOW_AUTODIFF_TAMC
100 act1 = bi - myBxLo(myThid)
101 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
102 act2 = bj - myByLo(myThid)
103 max2 = myByHi(myThid) - myByLo(myThid) + 1
104 act3 = myThid - 1
105 max3 = nTx*nTy
106 act4 = 0
107 ikey = (act1 + 1) + act2*max1
108 & + act3*max1*max2
109 & + act4*max1*max2*max3
110 #endif /* ALLOW_AUTODIFF_TAMC */
111
112 IF ( rkSign*gravitySign .GT. 0. ) THEN
113 C- <=> usingZCoords:
114 kTop = 2
115 kBottom = Nr
116 kDir = 1
117 deltaK = -1
118 ELSE
119 C- <=> usingPCoords:
120 kTop = Nr
121 kBottom = 2
122 kDir = -1
123 deltaK = 0
124 ENDIF
125
126 #ifdef ALLOW_AUTODIFF_TAMC
127 CADJ STORE theta(:,:,:,bi,bj) = tapelev_ini_bibj,
128 CADJ & key=ikey, byte=isbyte
129 CADJ STORE salt (:,:,:,bi,bj) = tapelev_ini_bibj,
130 CADJ & key=ikey, byte=isbyte
131 CADJ STORE convectcount(:,:,:) = tapelev_ini_bibj,
132 CADJ & key=ikey, byte=isbyte
133 #endif
134
135 C-- Loop over all *interior* layers
136 DO K=kTop,kBottom,kDir
137
138 #ifdef ALLOW_AUTODIFF_TAMC
139 kkey = (ikey-1)*Nr + k
140 CADJ STORE theta(:,:,k-1,bi,bj) = tapelev_ini_bibj_k,
141 CADJ & key=kkey, byte=isbyte
142 CADJ STORE salt (:,:,k-1,bi,bj) = tapelev_ini_bibj_k,
143 CADJ & key=kkey, byte=isbyte
144 CADJ STORE convectcount(:,:,k-1) = tapelev_ini_bibj_k,
145 CADJ & key=kkey, byte=isbyte
146 #endif /* ALLOW_AUTODIFF_TAMC */
147 C- Density of K-1 layer (above W(K)) reference to K-1 T-level
148 CALL FIND_RHO_2D(
149 I iMin, iMax, jMin, jMax, K+deltaK,
150 I theta(1-OLx,1-OLy,K-1,bi,bj),
151 I salt (1-OLx,1-OLy,K-1,bi,bj),
152 O rhoKm1,
153 I K-1, bi, bj, myThid )
154
155 C- Density of K layer (below W(K)) reference to K-1 T-level.
156 #ifdef ALLOW_AUTODIFF_TAMC
157 CADJ STORE theta(:,:,k,bi,bj) = tapelev_ini_bibj_k,
158 CADJ & key = kkey, byte = isbyte
159 CADJ STORE salt (:,:,k,bi,bj) = tapelev_ini_bibj_k,
160 CADJ & key = kkey, byte = isbyte
161 #endif /* ALLOW_AUTODIFF_TAMC */
162 CALL FIND_RHO_2D(
163 I iMin, iMax, jMin, jMax, K+deltaK,
164 I theta(1-OLx,1-OLy,K,bi,bj),
165 I salt (1-OLx,1-OLy,K,bi,bj),
166 O rhoK,
167 I K, bi, bj, myThid )
168
169 #ifdef ALLOW_AUTODIFF_TAMC
170 CADJ STORE rhoKm1(:,:) = tapelev_ini_bibj_k, key=kkey, byte=isbyte
171 CADJ STORE rhoK (:,:) = tapelev_ini_bibj_k, key=kkey, byte=isbyte
172 #endif /* ALLOW_AUTODIFF_TAMC */
173 C- Check static stability with layer below and mix as needed.
174 c CALL CONVECT(
175 c I bi,bj,iMin,iMax,jMin,jMax,K,rhoKm1,rhoK,
176 c U ConvectCount,
177 c I myTime,myIter,myThid)
178
179 C- Pre-calculate mixing weights for interface K
180 CALL CONVECTIVE_WEIGHTS(
181 I bi,bj,K,rhoKm1,rhoK,
182 O weightA,weightB,ConvectCount,
183 I myThid)
184
185 C- Convectively mix heat across interface K
186 CALL CONVECTIVELY_MIXTRACER(
187 I bi,bj,k,weightA,weightB,
188 U theta,
189 I myThid)
190
191 C- Convectively mix salt across interface K
192 CALL CONVECTIVELY_MIXTRACER(
193 I bi,bj,k,weightA,weightB,
194 U salt,
195 I myThid)
196
197 #ifdef ALLOW_PTRACERS
198 C- Convectively mix passive tracers across interface K
199 IF ( usePTRACERS ) THEN
200 CALL PTRACERS_CONVECT(
201 I bi,bj,k,weightA,weightB,myThid)
202 ENDIF
203 #endif /* ALLOW_PTRACERS */
204
205 C-- End DO K=1,Nr
206 ENDDO
207
208 C-- End IF (DIFFERENT_MULTIPLE)
209 ENDIF
210
211 #endif /* INCLUDE_CONVECT_CALL */
212
213 RETURN
214 END

  ViewVC Help
Powered by ViewVC 1.1.22