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

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

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


Revision 1.4 - (hide annotations) (download)
Thu Feb 23 20:55:49 2006 UTC (18 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58d_post, checkpoint58c_post, checkpoint58b_post
Changes since 1.3: +3 -1 lines
1rst implementation of  Implicit IGW using the 3-D solver (use3Dsolver=T)
 and based on the reference stratification

1 jmc 1.4 C $Header: /u/gcmpack/MITgcm/model/src/momentum_correction_step.F,v 1.3 2005/12/08 15:44:34 heimbach Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "PACKAGES_CONFIG.h"
5     #include "CPP_OPTIONS.h"
6    
7     CBOP
8     C !ROUTINE: MOMENTUM_CORRECTION_STEP
9     C !INTERFACE:
10     SUBROUTINE MOMENTUM_CORRECTION_STEP(myTime, myIter, myThid)
11     C !DESCRIPTION: \bv
12     C *==========================================================*
13 jmc 1.2 C | SUBROUTINE MOMENTUM_CORRECTION_STEP
14 jmc 1.1 C *==========================================================*
15     C |1rst Part : Update U,V.
16     C |
17     C | The arrays used for time stepping are cycled.
18     C | Momentum:
19     C | V(n) = Gv(n) - dt * grad Eta
20     C |
21     C |part1: update U,V
22     C | U*,V* (contained in gU,gV) have the surface
23     C | pressure gradient term added and the result stored
24     C | in U,V (contained in uVel, vVel)
25     C |
26     C |part2: Adjustments
27     C | o Filter U,V (Shapiro Filter, Zonal_Filter)
28     C | o Compute again Eta (exact volume conservation)
29     C | o Compute vertical velocity
30     C *==========================================================*
31     C \ev
32    
33     C !USES:
34     IMPLICIT NONE
35     C == Global variables ===
36     #include "SIZE.h"
37     #include "EEPARAMS.h"
38     #include "PARAMS.h"
39     #include "DYNVARS.h"
40    
41     #ifdef ALLOW_SHAP_FILT
42     #include "SHAP_FILT.h"
43     #endif
44 jmc 1.2 #ifdef ALLOW_ZONAL_FILT
45 jmc 1.1 #include "ZONAL_FILT.h"
46     #endif
47 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
48     #include "tamc.h"
49     #endif
50 jmc 1.1
51     C !INPUT/OUTPUT PARAMETERS:
52     C == Routine arguments ==
53     C myTime - Current time in simulation
54     C myIter - Current iteration number in simulation
55     C myThid - Thread number for this instance of the routine.
56     _RL myTime
57     INTEGER myIter
58     INTEGER myThid
59    
60     C !LOCAL VARIABLES:
61     C == Local variables
62     _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63     _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64     INTEGER iMin,iMax
65     INTEGER jMin,jMax
66     INTEGER bi,bj
67     INTEGER k,i,j
68    
69     CEOP
70    
71     DO bj=myByLo(myThid),myByHi(myThid)
72     DO bi=myBxLo(myThid),myBxHi(myThid)
73    
74     C-- Set up work arrays that need valid initial values
75     DO j=1-OLy,sNy+OLy
76     DO i=1-OLx,sNx+OLx
77     phiSurfX(i,j)=0.
78     phiSurfY(i,j)=0.
79     ENDDO
80     ENDDO
81    
82     C Loop range: Gradients of Eta are evaluated so valid
83     C range is all but first row and column in overlaps.
84     iMin = 1-OLx+1
85     iMax = sNx+OLx
86     jMin = 1-OLy+1
87     jMax = sNy+OLy
88    
89     C- Calculate gradient of surface Potentiel
90     CALL CALC_GRAD_PHI_SURF(
91     I bi,bj,iMin,iMax,jMin,jMax,
92     I etaN,
93     O phiSurfX,phiSurfY,
94     I myThid )
95    
96     C-- Loop over all layers, top to bottom
97     DO K=1,Nr
98    
99     C- Update velocity fields: V(n) = V** - dt * grad Eta
100     IF (momStepping)
101     & CALL CORRECTION_STEP(
102     I bi,bj,iMin,iMax,jMin,jMax,K,
103     I phiSurfX,phiSurfY,myTime,myThid )
104    
105     #ifdef ALLOW_OBCS
106     IF (useOBCS) THEN
107     CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
108     ENDIF
109     #endif /* ALLOW_OBCS */
110    
111     C-- End DO K=1,Nr
112     ENDDO
113    
114     C-- End of 1rst bi,bj loop
115     ENDDO
116     ENDDO
117    
118     C--- 2nd Part : Adjustment.
119    
120     C-- Filter (and exchange)
121     #ifdef ALLOW_SHAP_FILT
122     IF (useSHAP_FILT) THEN
123 jmc 1.2 IF ( .NOT.shap_filt_uvStar ) THEN
124     CALL TIMER_START('SHAP_FILT_UV [MOM_CORR_STEP]',myThid)
125     CALL SHAP_FILT_APPLY_UV( uVel, vVel, myTime, myIter, myThid )
126     CALL TIMER_STOP ('SHAP_FILT_UV [MOM_CORR_STEP]',myThid)
127     ENDIF
128 jmc 1.1 ENDIF
129 jmc 1.2 #endif
130 jmc 1.1 #ifdef ALLOW_ZONAL_FILT
131     IF (useZONAL_FILT) THEN
132 jmc 1.2 IF ( .NOT.zonal_filt_uvStar ) THEN
133     CALL TIMER_START('ZONAL_FILT_UV [MOM_CORR_STEP]',myThid)
134     CALL ZONAL_FILT_APPLY_UV( uVel, vVel, myThid )
135     CALL TIMER_STOP ('ZONAL_FILT_UV [MOM_CORR_STEP]',myThid)
136     ENDIF
137 jmc 1.1 ENDIF
138 jmc 1.2 #endif
139 jmc 1.1
140 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
141     # ifdef NONLIN_FRSURF
142     cph-test
143     CADJ STORE uvel, vvel = comlev1, key = ikey_dynamics
144     # endif
145     #endif
146 jmc 1.1 DO bj=myByLo(myThid),myByHi(myThid)
147     DO bi=myBxLo(myThid),myBxHi(myThid)
148    
149     C-- Integrate continuity vertically
150     C-- for vertical velocity and "etaN" (exact volume conservation) :
151     CALL INTEGR_CONTINUITY( bi, bj, uVel, vVel,
152     I myTime, myIter, myThid )
153    
154     C-- End of 2nd bi,bj loop
155     ENDDO
156     ENDDO
157    
158     IF ( exactConserv .AND. implicDiv2Dflow .NE. 0. _d 0)
159     & _EXCH_XY_R8( etaN , myThid )
160 jmc 1.4 IF ( implicitIntGravWave )
161     & _EXCH_XYZ_R8( wVel , myThid )
162 jmc 1.1
163     RETURN
164     END

  ViewVC Help
Powered by ViewVC 1.1.22