/[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.5 - (hide annotations) (download)
Wed May 3 23:34:42 2006 UTC (18 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint58e_post, mitgcm_mapl_00, checkpoint58u_post, checkpoint58w_post, checkpoint60, checkpoint61, checkpoint58r_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58q_post, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58f_post, checkpoint58i_post, checkpoint58g_post, checkpoint58o_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint61f, checkpoint61g, checkpoint61d, checkpoint61e, checkpoint61b, checkpoint61c, checkpoint58p_post, checkpoint61a, checkpoint61h, checkpoint61i, checkpoint58m_post
Changes since 1.4: +26 -2 lines
o Now rstar adjoint.

1 heimbach 1.5 C $Header: /u/gcmpack/MITgcm/model/src/momentum_correction_step.F,v 1.4 2006/02/23 20:55:49 jmc 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 heimbach 1.5 #include "tamc_keys.h"
50     # ifdef NONLIN_FRSURF
51     # include "SURFACE.h"
52     # endif
53 heimbach 1.3 #endif
54 jmc 1.1
55     C !INPUT/OUTPUT PARAMETERS:
56     C == Routine arguments ==
57     C myTime - Current time in simulation
58     C myIter - Current iteration number in simulation
59     C myThid - Thread number for this instance of the routine.
60     _RL myTime
61     INTEGER myIter
62     INTEGER myThid
63    
64     C !LOCAL VARIABLES:
65     C == Local variables
66     _RL phiSurfX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
67     _RL phiSurfY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
68     INTEGER iMin,iMax
69     INTEGER jMin,jMax
70     INTEGER bi,bj
71     INTEGER k,i,j
72    
73     CEOP
74    
75     DO bj=myByLo(myThid),myByHi(myThid)
76     DO bi=myBxLo(myThid),myBxHi(myThid)
77    
78     C-- Set up work arrays that need valid initial values
79     DO j=1-OLy,sNy+OLy
80     DO i=1-OLx,sNx+OLx
81     phiSurfX(i,j)=0.
82     phiSurfY(i,j)=0.
83     ENDDO
84     ENDDO
85    
86     C Loop range: Gradients of Eta are evaluated so valid
87     C range is all but first row and column in overlaps.
88     iMin = 1-OLx+1
89     iMax = sNx+OLx
90     jMin = 1-OLy+1
91     jMax = sNy+OLy
92    
93     C- Calculate gradient of surface Potentiel
94     CALL CALC_GRAD_PHI_SURF(
95     I bi,bj,iMin,iMax,jMin,jMax,
96     I etaN,
97     O phiSurfX,phiSurfY,
98     I myThid )
99    
100     C-- Loop over all layers, top to bottom
101     DO K=1,Nr
102    
103     C- Update velocity fields: V(n) = V** - dt * grad Eta
104     IF (momStepping)
105     & CALL CORRECTION_STEP(
106     I bi,bj,iMin,iMax,jMin,jMax,K,
107     I phiSurfX,phiSurfY,myTime,myThid )
108    
109     #ifdef ALLOW_OBCS
110     IF (useOBCS) THEN
111     CALL OBCS_APPLY_UV(bi,bj,K,uVel,vVel,myThid)
112     ENDIF
113     #endif /* ALLOW_OBCS */
114    
115     C-- End DO K=1,Nr
116     ENDDO
117    
118     C-- End of 1rst bi,bj loop
119     ENDDO
120     ENDDO
121    
122     C--- 2nd Part : Adjustment.
123    
124     C-- Filter (and exchange)
125     #ifdef ALLOW_SHAP_FILT
126     IF (useSHAP_FILT) THEN
127 jmc 1.2 IF ( .NOT.shap_filt_uvStar ) THEN
128     CALL TIMER_START('SHAP_FILT_UV [MOM_CORR_STEP]',myThid)
129     CALL SHAP_FILT_APPLY_UV( uVel, vVel, myTime, myIter, myThid )
130     CALL TIMER_STOP ('SHAP_FILT_UV [MOM_CORR_STEP]',myThid)
131     ENDIF
132 jmc 1.1 ENDIF
133 jmc 1.2 #endif
134 jmc 1.1 #ifdef ALLOW_ZONAL_FILT
135     IF (useZONAL_FILT) THEN
136 jmc 1.2 IF ( .NOT.zonal_filt_uvStar ) THEN
137     CALL TIMER_START('ZONAL_FILT_UV [MOM_CORR_STEP]',myThid)
138     CALL ZONAL_FILT_APPLY_UV( uVel, vVel, myThid )
139     CALL TIMER_STOP ('ZONAL_FILT_UV [MOM_CORR_STEP]',myThid)
140     ENDIF
141 jmc 1.1 ENDIF
142 jmc 1.2 #endif
143 jmc 1.1
144 heimbach 1.3 #ifdef ALLOW_AUTODIFF_TAMC
145     # ifdef NONLIN_FRSURF
146     CADJ STORE uvel, vvel = comlev1, key = ikey_dynamics
147     # endif
148     #endif
149 jmc 1.1 DO bj=myByLo(myThid),myByHi(myThid)
150     DO bi=myBxLo(myThid),myBxHi(myThid)
151    
152 heimbach 1.5 #ifdef ALLOW_AUTODIFF_TAMC
153     act1 = bi - myBxLo(myThid)
154     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
155     act2 = bj - myByLo(myThid)
156     max2 = myByHi(myThid) - myByLo(myThid) + 1
157     act3 = myThid - 1
158     max3 = nTx*nTy
159     act4 = ikey_dynamics - 1
160     idynkey = (act1 + 1) + act2*max1
161     & + act3*max1*max2
162     & + act4*max1*max2*max3
163     # ifdef NONLIN_FRSURF
164     # ifndef DISABLE_RSTAR_CODE
165     cph-test
166     CADJ STORE detahdt(:,:,bi,bj) = comlev1_bibj, key = idynkey, byte = isbyte
167     CADJ STORE etan(:,:,bi,bj) = comlev1_bibj, key = idynkey, byte = isbyte
168     CADJ STORE rstardhcdt(:,:,bi,bj) = comlev1_bibj, key = idynkey, byte = isbyte
169     # endif
170     # endif
171     #endif
172    
173 jmc 1.1 C-- Integrate continuity vertically
174     C-- for vertical velocity and "etaN" (exact volume conservation) :
175     CALL INTEGR_CONTINUITY( bi, bj, uVel, vVel,
176     I myTime, myIter, myThid )
177    
178     C-- End of 2nd bi,bj loop
179     ENDDO
180     ENDDO
181    
182     IF ( exactConserv .AND. implicDiv2Dflow .NE. 0. _d 0)
183     & _EXCH_XY_R8( etaN , myThid )
184 jmc 1.4 IF ( implicitIntGravWave )
185     & _EXCH_XYZ_R8( wVel , myThid )
186 jmc 1.1
187     RETURN
188     END

  ViewVC Help
Powered by ViewVC 1.1.22