/[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.19 - (show annotations) (download)
Mon Oct 7 16:24:45 2002 UTC (21 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint46l_pre, checkpoint46j_post, checkpoint46k_post
Changes since 1.18: +10 -17 lines
* split calc_exact_eta in 2 S/R : integr_continuity & update_etaH
* move wVel computation at the end of the time step, in S/R integr_continuity
* create specific S/R to exchange T,S before DYNAMICS (for stagger time step)
* update timeave pkg for wVel diagnostic ; put convertEmP2rUnit in PARAMS.h

1 C $Header: /u/gcmpack/MITgcm/model/src/the_correction_step.F,v 1.18 2002/03/04 17:26:41 adcroft 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 gT) is copied to T (theta)
29 C | S* (contained in gS) is copied to S (salt)
30 C |
31 C |part2: Adjustments & Diagnostics
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 Compute vertical velocity
36 C | o Diagmnostic of state variables (Time average)
37 C *==========================================================*
38 C \ev
39
40 C !USES:
41 IMPLICIT NONE
42 C == Global variables ===
43 #include "SIZE.h"
44 #include "EEPARAMS.h"
45 #include "PARAMS.h"
46 #include "DYNVARS.h"
47 #ifdef ALLOW_PASSIVE_TRACER
48 #include "TR1.h"
49 #endif
50
51 #ifdef ALLOW_SHAP_FILT
52 #include "SHAP_FILT.h"
53 #endif
54 #ifdef ALLOW_ZONAL_FILT
55 #include "ZONAL_FILT.h"
56 #endif
57
58 C !INPUT/OUTPUT PARAMETERS:
59 C == Routine arguments ==
60 C myTime - Current time in simulation
61 C myIter - Current iteration number in simulation
62 C myThid - Thread number for this instance of the routine.
63 _RL myTime
64 INTEGER myIter
65 INTEGER myThid
66
67 C !LOCAL VARIABLES:
68 C == Local variables
69 _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70 _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 INTEGER iMin,iMax
72 INTEGER jMin,jMax
73 INTEGER bi,bj
74 INTEGER k,i,j
75
76 CEOP
77
78 DO bj=myByLo(myThid),myByHi(myThid)
79 DO bi=myBxLo(myThid),myBxHi(myThid)
80
81 C-- Set up work arrays that need valid initial values
82 DO j=1-OLy,sNy+OLy
83 DO i=1-OLx,sNx+OLx
84 phiSurfX(i,j)=0.
85 phiSurfY(i,j)=0.
86 ENDDO
87 ENDDO
88
89 C Loop range: Gradients of Eta are evaluated so valid
90 C range is all but first row and column in overlaps.
91 iMin = 1-OLx+1
92 iMax = sNx+OLx
93 jMin = 1-OLy+1
94 jMax = sNy+OLy
95
96 C- Calculate gradient of surface Potentiel
97 CALL CALC_GRAD_PHI_SURF(
98 I bi,bj,iMin,iMax,jMin,jMax,
99 I etaN,
100 O phiSurfX,phiSurfY,
101 I myThid )
102
103 C-- Loop over all layers, top to bottom
104 DO K=1,Nr
105
106 C- Update velocity fields: V(n) = V** - dt * grad Eta
107 IF (momStepping)
108 & CALL CORRECTION_STEP(
109 I bi,bj,iMin,iMax,jMin,jMax,K,
110 I phiSurfX,phiSurfY,myTime,myThid )
111
112 C- Update tracer fields: T(n) = T**, Gt(n-1) = Gt(n)
113 IF (tempStepping)
114 & CALL CYCLE_TRACER(
115 I bi,bj,iMin,iMax,jMin,jMax,K,
116 U theta,gT,gTNm1,
117 I myTime,myThid )
118 IF (saltStepping)
119 & CALL CYCLE_TRACER(
120 I bi,bj,iMin,iMax,jMin,jMax,K,
121 U salt,gS,gSNm1,
122 I myTime,myThid )
123 #ifdef ALLOW_PASSIVE_TRACER
124 IF (tr1Stepping)
125 & CALL CYCLE_TRACER(
126 I bi,bj,iMin,iMax,jMin,jMax,K,
127 U Tr1,gTr1,gTr1Nm1,
128 I myTime,myThid )
129 #endif
130 #ifdef ALLOW_PTRACERS
131 C- Update passive tracer fields: T(n) = T**, Gt(n-1) = Gt(n)
132 IF (usePTRACERS)
133 & CALL PTRACERS_CYCLE(bi,bj,k,myIter,myTime,myThid)
134 #endif /* ALLOW_PTRACERS */
135
136
137 #ifdef ALLOW_OBCS
138 IF (useOBCS) THEN
139 CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
140 ENDIF
141 #endif /* ALLOW_OBCS */
142
143 C-- End DO K=1,Nr
144 ENDDO
145
146 C-- End of 1rst bi,bj loop
147 ENDDO
148 ENDDO
149
150 C--- 2nd Part : Adjustment.
151 C
152 C Static stability is calculated and the tracers are
153 C convective adjusted where statically unstable.
154
155 C-- Filter (and exchange)
156 #ifdef ALLOW_SHAP_FILT
157 IF (useSHAP_FILT) THEN
158 IF ( .NOT.shap_filt_uvStar )
159 & CALL SHAP_FILT_APPLY_UV( uVel, vVel, myTime, myIter, myThid )
160
161 IF ( .NOT.(staggerTimeStep .AND. shap_filt_TrStagg) )
162 & CALL SHAP_FILT_APPLY_TS( theta,salt, myTime, myIter, myThid )
163 ENDIF
164 #endif
165 #ifdef ALLOW_ZONAL_FILT
166 IF (useZONAL_FILT) THEN
167 IF ( .NOT.zonal_filt_uvStar )
168 & CALL ZONAL_FILT_APPLY_UV( uVel, vVel, myThid )
169
170 IF ( .NOT.(staggerTimeStep .AND. zonal_filt_TrStagg) )
171 & CALL ZONAL_FILT_APPLY_TS( theta, salt, myThid )
172
173 ENDIF
174 #endif
175
176 DO bj=myByLo(myThid),myByHi(myThid)
177 DO bi=myBxLo(myThid),myBxHi(myThid)
178
179 C-- Convectively adjust new fields to be statically stable
180 iMin = 1-OLx+1
181 iMax = sNx+OLx
182 jMin = 1-OLy+1
183 jMax = sNy+OLy
184 CALL CONVECTIVE_ADJUSTMENT(
185 I bi, bj, iMin, iMax, jMin, jMax,
186 I myTime, myIter, myThid )
187
188 C-- Integrate continuity vertically
189 C-- for vertical velocity and "etaN" (exact volume conservation) :
190 CALL INTEGR_CONTINUITY( bi, bj, uVel, vVel,
191 I myTime, myIter, myThid )
192
193 #ifdef ALLOW_TIMEAVE
194 IF (taveFreq.GT.0.) THEN
195 CALL TIMEAVE_STATVARS(myTime, myIter, bi, bj, myThid)
196 ENDIF
197 #endif /* ALLOW_TIMEAVE */
198
199 C-- End of 2nd bi,bj loop
200 ENDDO
201 ENDDO
202
203 RETURN
204 END

  ViewVC Help
Powered by ViewVC 1.1.22