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

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

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


Revision 1.15 - (show annotations) (download)
Thu Sep 27 20:12:10 2001 UTC (23 years ago) by heimbach
Branch: MAIN
CVS Tags: release1_b1, checkpoint43, ecco-branch-mod1, release1_beta1, checkpoint42
Branch point for: release1_coupled, release1, ecco-branch
Changes since 1.14: +4 -5 lines
Fixed AD-related problems:
o Store directives up-to-date with re-arranged Adams-Bashforth
  (mainly thermodynamics.F)
o New store directives for multi-dim. advection schemes
  * new CPP flag ALLOW_MULTI_DIM_ADVECTION
  * new common block and key passkey
  (mainly gad_advection.F)
o Modified store directives for split of dynamics/thermodynamics
  for the case ALLOW_KPP
o Cleaned argument list for timestep_tracer.F

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/the_correction_step.F,v 1.14 2001/09/26 18:09:16 cnh Exp $
2 C Tag $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: THE_CORRECTION_STEP
8 C !INTERFACE:
9 SUBROUTINE THE_CORRECTION_STEP(myTime, myIter, myThid)
10 C !DESCRIPTION: \bv
11 C *==========================================================*
12 C | SUBROUTINE THE_CORRECTION_STEP
13 C *==========================================================*
14 C |1rst Part : Update U,V,T,S.
15 C |
16 C | The arrays used for time stepping are cycled.
17 C | Tracers:
18 C | T(n) = Gt(n-1)
19 C | Gt(n-1) = Gt(n)
20 C | Momentum:
21 C | V(n) = Gv(n-1) - dt * grad Eta
22 C | Gv(n-1) = Gv(n)
23 C |
24 C |part1: update U,V,T,S
25 C | U*,V* (contained in gUnm1,gVnm1) have the surface
26 C | pressure gradient term added and the result stored
27 C | in U,V (contained in uVel, vVel)
28 C | T* (contained in gTnm1) is copied to T (theta)
29 C | S* (contained in gSnm1) is copied to S (salt)
30 C |
31 C |part2: Adjustments.
32 C | o Filter U,V,T,S (Shapiro Filter, Zonal_Filter)
33 C | o Convective Adjustment
34 C | o Compute again Eta (exact volume conservation)
35 C | o Diagmnostic of state variables (Time average)
36 C *==========================================================*
37 C \ev
38
39 C !USES:
40 IMPLICIT NONE
41 C == Global variables ===
42 #include "SIZE.h"
43 #include "EEPARAMS.h"
44 #include "PARAMS.h"
45 #include "DYNVARS.h"
46 #ifdef ALLOW_PASSIVE_TRACER
47 #include "TR1.h"
48 #endif
49 #ifdef ALLOW_AUTODIFF_TAMC
50 #include "tamc.h"
51 #include "tamc_keys.h"
52 #endif /* ALLOW_AUTODIFF_TAMC */
53
54 C !INPUT/OUTPUT PARAMETERS:
55 C == Routine arguments ==
56 C myTime - Current time in simulation
57 C myIter - Current iteration number in simulation
58 C myThid - Thread number for this instance of the routine.
59 _RL myTime
60 INTEGER myIter
61 INTEGER myThid
62
63 C !LOCAL VARIABLES:
64 C == Local variables
65 _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
66 _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67 INTEGER iMin,iMax
68 INTEGER jMin,jMax
69 INTEGER bi,bj
70 INTEGER k,i,j
71
72 CEOP
73
74 DO bj=myByLo(myThid),myByHi(myThid)
75 DO bi=myBxLo(myThid),myBxHi(myThid)
76
77 #ifdef ALLOW_AUTODIFF_TAMC
78 act1 = bi - myBxLo(myThid)
79 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
80 act2 = bj - myByLo(myThid)
81 max2 = myByHi(myThid) - myByLo(myThid) + 1
82 act3 = myThid - 1
83 max3 = nTx*nTy
84 act4 = ikey_dynamics - 1
85 ikey = (act1 + 1) + act2*max1
86 & + act3*max1*max2
87 & + act4*max1*max2*max3
88 #endif /* ALLOW_AUTODIFF_TAMC */
89
90 C-- Set up work arrays that need valid initial values
91 DO j=1-OLy,sNy+OLy
92 DO i=1-OLx,sNx+OLx
93 phiSurfX(i,j)=0.
94 phiSurfY(i,j)=0.
95 ENDDO
96 ENDDO
97
98 C Loop range: Gradients of Eta are evaluated so valid
99 C range is all but first row and column in overlaps.
100 iMin = 1-OLx+1
101 iMax = sNx+OLx
102 jMin = 1-OLy+1
103 jMax = sNy+OLy
104
105 C- Calculate gradient of surface Potentiel
106 CALL CALC_GRAD_PHI_SURF(
107 I bi,bj,iMin,iMax,jMin,jMax,
108 I etaN,
109 O phiSurfX,phiSurfY,
110 I myThid )
111
112 C-- Loop over all layers, top to bottom
113 DO K=1,Nr
114
115 #ifdef ALLOW_AUTODIFF_TAMC
116 kkey = (ikey-1)*Nr + k
117 #endif
118
119 C- Update velocity fields: V(n) = V** - dt * grad Eta
120 IF (momStepping)
121 & CALL CORRECTION_STEP(
122 I bi,bj,iMin,iMax,jMin,jMax,K,
123 I phiSurfX,phiSurfY,myTime,myThid )
124
125 C- Update tracer fields: T(n) = T**, Gt(n-1) = Gt(n)
126 IF (tempStepping)
127 & CALL CYCLE_TRACER(
128 I bi,bj,iMin,iMax,jMin,jMax,K,
129 U theta,gT,gTNm1,
130 I myTime,myThid )
131 IF (saltStepping)
132 & CALL CYCLE_TRACER(
133 I bi,bj,iMin,iMax,jMin,jMax,K,
134 U salt,gS,gSNm1,
135 I myTime,myThid )
136 #ifdef ALLOW_PASSIVE_TRACER
137 IF (tr1Stepping)
138 & CALL CYCLE_TRACER(
139 I bi,bj,iMin,iMax,jMin,jMax,K,
140 U Tr1,gTr1,gTr1Nm1,
141 I myTime,myThid )
142 #endif
143
144 #ifdef ALLOW_OBCS
145 #ifdef ALLOW_AUTODIFF_TAMC
146 CADJ STORE uvel (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
147 CADJ STORE vvel (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
148 CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
149 CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
150 #ifdef ALLOW_PASSIVE_TRACER
151 CADJ STORE tr1 (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
152 #endif
153 #endif /* ALLOW_AUTODIFF_TAMC */
154 IF (useOBCS) THEN
155 CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
156 ENDIF
157 #endif /* ALLOW_OBCS */
158
159 C-- End DO K=1,Nr
160 ENDDO
161
162 C-- End of 1rst bi,bj loop
163 ENDDO
164 ENDDO
165
166 C--- 2nd Part : Adjustment.
167 C
168 C Static stability is calculated and the tracers are
169 C convective adjusted where statically unstable.
170
171 #ifdef ALLOW_SHAP_FILT
172 IF (useSHAP_FILT) THEN
173 C-- Filter (and exchange).
174 CALL SHAP_FILT_APPLY(
175 I uVel, vVel, theta, salt,
176 I myTime, myIter, myThid )
177 ENDIF
178 #endif
179
180 #ifdef ALLOW_ZONAL_FILT
181 IF (zonal_filt_lat.LT.90.) THEN
182 CALL ZONAL_FILT_APPLY(
183 U uVel, vVel, theta, salt,
184 I myThid )
185 ENDIF
186 #endif
187
188 DO bj=myByLo(myThid),myByHi(myThid)
189 DO bi=myBxLo(myThid),myBxHi(myThid)
190
191 C-- Convectively adjust new fields to be statically stable
192 iMin = 1-OLx+1
193 iMax = sNx+OLx
194 jMin = 1-OLy+1
195 jMax = sNy+OLy
196 CALL CONVECTIVE_ADJUSTMENT(
197 I bi, bj, iMin, iMax, jMin, jMax,
198 I myTime, myIter, myThid )
199
200 #ifdef EXACT_CONSERV
201 IF (exactConserv) THEN
202 C-- Compute again "eta" to satisfy exactly the total Volume Conservation :
203 CALL CALC_EXACT_ETA( .TRUE., bi,bj, uVel,vVel,
204 I myTime, myIter, myThid )
205 ENDIF
206 #endif /* EXACT_CONSERV */
207
208 #ifdef ALLOW_TIMEAVE
209 IF (taveFreq.GT.0.) THEN
210 CALL TIMEAVE_STATVARS(myTime, myIter, bi, bj, myThid)
211 ENDIF
212 #endif /* ALLOW_TIMEAVE */
213
214 C-- End of 2nd bi,bj loop
215 ENDDO
216 ENDDO
217
218 #ifdef EXACT_CONSERV
219 IF (exactConserv .AND. implicDiv2Dflow .NE. 0. _d 0)
220 & _EXCH_XY_R8(etaN, myThid )
221 #endif /* EXACT_CONSERV */
222
223 RETURN
224 END

  ViewVC Help
Powered by ViewVC 1.1.22