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

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

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


Revision 1.15.4.3 - (hide annotations) (download)
Fri Mar 7 23:10:21 2003 UTC (21 years, 2 months ago) by heimbach
Branch: ecco-branch
CVS Tags: ecco_c50_e32, ecco_c50_e33, ecco_c50_e30, ecco_c50_e31, ecco_c50_e29, ecco_c50_e28, ecco_c50_e33a
Changes since 1.15.4.2: +20 -21 lines
merging c49 and e27

1 heimbach 1.15.4.3 C $Header: /u/gcmpack/MITgcm/model/src/the_correction_step.F,v 1.20 2002/11/01 22:00:33 mlosch Exp $
2 jmc 1.13 C Tag $Name: $
3 adcroft 1.2
4     #include "CPP_OPTIONS.h"
5    
6 cnh 1.14 CBOP
7     C !ROUTINE: THE_CORRECTION_STEP
8     C !INTERFACE:
9 adcroft 1.2 SUBROUTINE THE_CORRECTION_STEP(myTime, myIter, myThid)
10 cnh 1.14 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 heimbach 1.15.4.3 C | T* (contained in gT) is copied to T (theta)
29     C | S* (contained in gS) is copied to S (salt)
30 cnh 1.14 C |
31 heimbach 1.15.4.3 C |part2: Adjustments & Diagnostics
32 cnh 1.14 C | o Filter U,V,T,S (Shapiro Filter, Zonal_Filter)
33     C | o Convective Adjustment
34 heimbach 1.15.4.3 C | o Compute again Eta (exact volume conservation)
35     C | o Compute vertical velocity
36 cnh 1.14 C | o Diagmnostic of state variables (Time average)
37     C *==========================================================*
38     C \ev
39    
40     C !USES:
41 adcroft 1.2 IMPLICIT NONE
42     C == Global variables ===
43     #include "SIZE.h"
44     #include "EEPARAMS.h"
45     #include "PARAMS.h"
46     #include "DYNVARS.h"
47 heimbach 1.12 #ifdef ALLOW_PASSIVE_TRACER
48 heimbach 1.11 #include "TR1.h"
49 heimbach 1.12 #endif
50 heimbach 1.15.4.1
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 cnh 1.14 C !INPUT/OUTPUT PARAMETERS:
59 adcroft 1.2 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 cnh 1.14 C !LOCAL VARIABLES:
68 adcroft 1.2 C == Local variables
69 jmc 1.6 _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
70     _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
71 adcroft 1.2 INTEGER iMin,iMax
72     INTEGER jMin,jMax
73     INTEGER bi,bj
74     INTEGER k,i,j
75    
76 cnh 1.14 CEOP
77 adcroft 1.9
78 adcroft 1.2 DO bj=myByLo(myThid),myByHi(myThid)
79     DO bi=myBxLo(myThid),myBxHi(myThid)
80 heimbach 1.7
81 adcroft 1.2 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 jmc 1.6 phiSurfX(i,j)=0.
85     phiSurfY(i,j)=0.
86 adcroft 1.2 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 jmc 1.6 C- Calculate gradient of surface Potentiel
97     CALL CALC_GRAD_PHI_SURF(
98 adcroft 1.2 I bi,bj,iMin,iMax,jMin,jMax,
99 jmc 1.5 I etaN,
100 jmc 1.6 O phiSurfX,phiSurfY,
101 adcroft 1.2 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 adcroft 1.3 IF (momStepping)
108     & CALL CORRECTION_STEP(
109 adcroft 1.2 I bi,bj,iMin,iMax,jMin,jMax,K,
110 jmc 1.6 I phiSurfX,phiSurfY,myTime,myThid )
111 adcroft 1.2
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 heimbach 1.11 I myTime,myThid )
123 heimbach 1.12 #ifdef ALLOW_PASSIVE_TRACER
124 heimbach 1.11 IF (tr1Stepping)
125     & CALL CYCLE_TRACER(
126     I bi,bj,iMin,iMax,jMin,jMax,K,
127     U Tr1,gTr1,gTr1Nm1,
128 adcroft 1.2 I myTime,myThid )
129 heimbach 1.12 #endif
130 heimbach 1.15.4.3 #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 adcroft 1.2
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 adcroft 1.9 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 heimbach 1.15.4.1 C-- Filter (and exchange)
156 adcroft 1.9 #ifdef ALLOW_SHAP_FILT
157     IF (useSHAP_FILT) THEN
158 heimbach 1.15.4.1 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 adcroft 1.9 ENDIF
164     #endif
165     #ifdef ALLOW_ZONAL_FILT
166 heimbach 1.15.4.1 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 adcroft 1.9 ENDIF
174     #endif
175    
176     DO bj=myByLo(myThid),myByHi(myThid)
177     DO bi=myBxLo(myThid),myBxHi(myThid)
178    
179 adcroft 1.2 C-- Convectively adjust new fields to be statically stable
180 heimbach 1.15.4.3 iMin = 1
181     iMax = sNx
182     jMin = 1
183     jMax = sNy
184 adcroft 1.2 CALL CONVECTIVE_ADJUSTMENT(
185     I bi, bj, iMin, iMax, jMin, jMax,
186     I myTime, myIter, myThid )
187 jmc 1.4
188 heimbach 1.15.4.3 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 adcroft 1.9
193 jmc 1.5 #ifdef ALLOW_TIMEAVE
194 jmc 1.4 IF (taveFreq.GT.0.) THEN
195 jmc 1.5 CALL TIMEAVE_STATVARS(myTime, myIter, bi, bj, myThid)
196 jmc 1.4 ENDIF
197 jmc 1.5 #endif /* ALLOW_TIMEAVE */
198 adcroft 1.2
199 adcroft 1.9 C-- End of 2nd bi,bj loop
200 adcroft 1.2 ENDDO
201     ENDDO
202    
203     RETURN
204     END

  ViewVC Help
Powered by ViewVC 1.1.22