/[MITgcm]/MITgcm/pkg/mom_fluxform/mom_cdscheme.F
ViewVC logotype

Contents of /MITgcm/pkg/mom_fluxform/mom_cdscheme.F

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


Revision 1.7 - (show annotations) (download)
Thu Apr 17 13:44:10 2003 UTC (21 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint51j_post, checkpoint50e_post, checkpoint50c_post, checkpoint50g_post, branchpoint-genmake2, checkpoint51e_post, checkpoint51b_post, checkpoint51f_pre, checkpoint50d_pre, checkpoint51, checkpoint50d_post, checkpoint51b_pre, checkpoint51h_pre, checkpoint50c_pre, checkpoint51g_post, checkpoint51f_post, checkpoint50b_post, checkpoint51c_post, checkpoint50f_post, checkpoint50f_pre, checkpoint51d_post, checkpoint50h_post, checkpoint51a_post, checkpoint50e_pre, checkpoint50i_post, checkpoint51i_pre
Branch point for: branch-genmake2
Changes since 1.6: +42 -26 lines
o to allow to put the momForcing out of the Adams-Bashforth:
  move forcing & CD-scheme calls from mom_fluxform & mom_vecinv
  to timestep.F
o new flag "useCDscheme" (default=F); replace guCD,gvCD by local arrays

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_fluxform/mom_cdscheme.F,v 1.6 2003/02/18 15:36:45 jmc Exp $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MOM_CDSCHEME
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE MOM_CDSCHEME(
11 I bi,bj,k, dPhiHydX,dPhiHydY, guFld,gvFld,
12 O guCor,gvCor,
13 I myTime, myIter, myThid)
14
15 C !DESCRIPTION:
16 C The C-D scheme. The less said the better :-)
17
18 C !USES: ===============================================================
19 C == Global variables ==
20 IMPLICIT NONE
21 #include "SIZE.h"
22 #include "DYNVARS.h"
23 #include "EEPARAMS.h"
24 #include "PARAMS.h"
25 #include "GRID.h"
26 #include "SURFACE.h"
27
28 C !INPUT PARAMETERS: ===================================================
29 C bi,bj :: tile indices
30 C k :: vertical level
31 C dPhiHydX,Y :: Gradient (X & Y dir.) of Hydrostatic Potential
32 C guFld,gvFld :: Acceleration (U & V compon.) from the C grid
33 C guCor,gvCor :: Coriolis terms (2 compon.) computed on C grid
34 C myTime :: current time
35 C myIter :: current time-step number
36 C myThid :: thread number
37
38 INTEGER bi,bj,k
39 _RL dPhiHydX(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
40 _RL dPhiHydY(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
41 _RL guFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
42 _RL gvFld(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
43 _RL guCor(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
44 _RL gvCor(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
45 _RL myTime
46 INTEGER myIter
47 INTEGER myThid
48
49
50 C !LOCAL VARIABLES: ====================================================
51 #ifdef INCLUDE_CD_CODE
52 C i,j :: loop indices
53 C pF :: pressure gradient
54 C vF :: work space
55 C aF :: work space
56 _RL pF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57 _RL vF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
58 _RL aF(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59 INTEGER i,j,iMin,iMax,jMin,jMax
60 _RL ab15,ab05
61 _RL phxFac, phyFac
62 CEOP
63
64 C Compute ranges
65 iMin=1-Olx+1
66 iMax=sNx+Olx-1
67 jMin=1-Oly+1
68 jMax=sNy+Oly-1
69
70 C Adams-Bashforth weighting factors
71 ab15 = 1.5 + abEps
72 ab05 = -0.5 - abEps
73
74 C-- stagger time stepping: grad Phi_Hyp is not in gU,gV and needs to be added:
75 IF (staggerTimeStep) THEN
76 phxFac = pfFacMom
77 phyFac = pfFacMom
78 ELSE
79 phxFac = 0.
80 phyFac = 0.
81 ENDIF
82
83 C- Initialize output (dummy) arrays:
84 c DO j=1-Oly,sNy+Oly
85 c DO i=1-Olx,sNx+Olx
86 c guCor(i,j) = 0. _d 0
87 c gvCor(i,j) = 0. _d 0
88 c ENDDO
89 c ENDDO
90
91 C Pressure extrapolated forward in time
92 DO j=1-Oly,sNy+Oly
93 DO i=1-Olx,sNx+Olx
94 pf(i,j) =
95 & ab15*( etaN(i,j,bi,bj)*Bo_surf(i,j,bi,bj) )
96 & +ab05*(etaNm1(i,j,bi,bj)*Bo_surf(i,j,bi,bj) )
97 ENDDO
98 ENDDO
99
100 C-- Zonal velocity coriolis term
101 C Note. As coded here, coriolis will not work with "thin walls"
102 C-- Coriolis with CD scheme allowed
103 C grady(p) + gV
104 DO j=1-Oly+1,sNy+Oly
105 DO i=1-Olx,sNx+Olx
106 af(i,j) = -_maskS(i,j,k,bi,bj)*(
107 & _recip_dyC(i,j,bi,bj)*(pf(i,j)-pf(i,j-1))
108 & +phyFac*dPhiHydY(i,j) )
109 & + gvFld(i,j)
110 ENDDO
111 ENDDO
112 C Average to Vd point and add coriolis
113 DO j=jMin,jMax
114 DO i=iMin,iMax
115 vf(i,j) =
116 & 0.25*( af(i ,j)+af(i ,j+1)
117 & +af(i-1,j)+af(i-1,j+1)
118 & )*_maskW(i,j,k,bi,bj)
119 & -0.5*(_fCori(i,j,bi,bj)+
120 & _fCori(i-1,j,bi,bj))
121 & *uVel(i,j,k,bi,bj)
122 ENDDO
123 ENDDO
124 C Step forward Vd
125 DO j=jMin,jMax
126 DO i=iMin,iMax
127 vVelD(i,j,k,bi,bj) = vVelD(i,j,k,bi,bj) + deltaTmom*vf(i,j)
128 ENDDO
129 ENDDO
130 C Relax D grid V to C grid V
131 DO j=jMin,jMax
132 DO i=iMin,iMax
133 vVelD(i,j,k,bi,bj) = ( rCD*vVelD(i,j,k,bi,bj)
134 & +(1. - rCD)*(
135 & ab15*(
136 & vVel(i ,j ,k,bi,bj)+vVel(i ,j+1,k,bi,bj)
137 & +vVel(i-1,j ,k,bi,bj)+vVel(i-1,j+1,k,bi,bj)
138 & )*0.25
139 & +ab05*(
140 & vNM1(i ,j ,k,bi,bj)+vNM1(i ,j+1,k,bi,bj)
141 & +vNM1(i-1,j ,k,bi,bj)+vNM1(i-1,j+1,k,bi,bj)
142 & )*0.25
143 & ) )*_maskW(i,j,k,bi,bj)
144 ENDDO
145 ENDDO
146 C Calculate coriolis force on U
147 DO j=jMin,jMax
148 DO i=iMin,iMax
149 guCor(i,j) =
150 & 0.5*( _fCori(i ,j,bi,bj) +
151 & _fCori(i-1,j,bi,bj) )
152 & *vVelD(i,j,k,bi,bj)*cfFacMom
153 ENDDO
154 ENDDO
155
156 C-- Meridional velocity coriolis term
157 C gradx(p)+gU
158 DO j=1-Oly,sNy+Oly
159 DO i=1-Olx+1,sNx+Olx
160 af(i,j) = -_maskW(i,j,k,bi,bj)*(
161 & _recip_dxC(i,j,bi,bj)*(pf(i,j)-pf(i-1,j))
162 & +phxFac*dPhiHydX(i,j) )
163 & + guFld(i,j)
164 ENDDO
165 ENDDO
166 C Average to Ud point and add coriolis
167 DO j=jMin,jMax
168 DO i=iMin,iMax
169 vf(i,j) =
170 & 0.25*( af(i ,j)+af(i ,j-1)
171 & +af(i+1,j)+af(i+1,j-1)
172 & )*_maskS(i,j,k,bi,bj)
173 & +0.5*( _fCori(i,j,bi,bj)
174 & +_fCori(i,j-1,bi,bj))
175 & *vVel(i,j,k,bi,bj)
176 ENDDO
177 ENDDO
178 C Step forward Ud
179 DO j=jMin,jMax
180 DO i=iMin,iMax
181 uVelD(i,j,k,bi,bj) = uVelD(i,j,k,bi,bj) + deltaTmom*vf(i,j)
182 ENDDO
183 ENDDO
184 C Relax D grid U to C grid U
185 DO j=jMin,jMax
186 DO i=iMin,iMax
187 uVelD(i,j,k,bi,bj) = ( rCD*uVelD(i,j,k,bi,bj)
188 & +(1. - rCD)*(
189 & ab15*(
190 & uVel(i,j ,k,bi,bj)+uVel(i+1,j ,k,bi,bj)
191 & +uVel(i,j-1,k,bi,bj)+uVel(i+1,j-1,k,bi,bj)
192 & )*0.25
193 & +ab05*(
194 & uNM1(i,j ,k,bi,bj)+uNM1(i+1,j ,k,bi,bj)
195 & +uNM1(i,j-1,k,bi,bj)+uNM1(i+1,j-1,k,bi,bj)
196 & )*0.25
197 & ) )*_maskS(i,j,k,bi,bj)
198 ENDDO
199 ENDDO
200 C Calculate coriolis force on V
201 DO j=jMin,jMax
202 DO i=iMin,iMax
203 gvCor(i,j) =
204 & -0.5*( _fCori(i ,j,bi,bj)
205 & +_fCori(i,j-1,bi,bj) )
206 & *uVelD(i,j,k,bi,bj)*cfFacMom
207 ENDDO
208 ENDDO
209
210 C-- Save "previous time level" variables
211 DO j=1-OLy,sNy+OLy
212 DO i=1-OLx,sNx+OLx
213 uNM1(i,j,k,bi,bj) = uVel(i,j,k,bi,bj)
214 vNM1(i,j,k,bi,bj) = vVel(i,j,k,bi,bj)
215 ENDDO
216 ENDDO
217
218 #endif /* INCLUDE_CD_CODE */
219
220 RETURN
221 END

  ViewVC Help
Powered by ViewVC 1.1.22