/[MITgcm]/MITgcm/pkg/mom_vecinv/mom_vi_v_vertshear.F
ViewVC logotype

Annotation of /MITgcm/pkg/mom_vecinv/mom_vi_v_vertshear.F

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


Revision 1.6 - (hide annotations) (download)
Thu Jun 9 15:59:20 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57i_post
Changes since 1.5: +24 -14 lines
vertical advection term use upwind bias interp. (if upwindShear=T)

1 jmc 1.6 C $Header: /u/gcmpack/MITgcm/pkg/mom_vecinv/mom_vi_v_vertshear.F,v 1.5 2004/07/20 17:46:38 adcroft Exp $
2 jmc 1.3 C $Name: $
3 adcroft 1.2
4 adcroft 1.5 #include "MOM_VECINV_OPTIONS.h"
5 adcroft 1.2
6     SUBROUTINE MOM_VI_V_VERTSHEAR(
7     I bi,bj,K,
8     I vFld,wFld,
9     U vShearTerm,
10     I myThid)
11     IMPLICIT NONE
12     C /==========================================================\
13     C | S/R MOM_V_VERTSHEAR |
14     C |==========================================================|
15     C \==========================================================/
16    
17     C == Global variables ==
18     #include "SIZE.h"
19     #include "EEPARAMS.h"
20     #include "GRID.h"
21     #include "PARAMS.h"
22    
23     C == Routine arguments ==
24     INTEGER bi,bj,K
25     _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
26     _RL wFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
27     _RL vShearTerm(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
28     INTEGER myThid
29    
30     C == Local variables ==
31     INTEGER I,J,Kp1,Km1
32     _RL mask_Kp1,mask_Km1,wBarYm,wBarYp
33 jmc 1.6 _RL vZm,vZp
34     c _RL vmask_Kp1,vmask_K,vmask_Km1
35     c LOGICAL freeslipK,noslipK
36     c PARAMETER(freeslipK=.TRUE.)
37     c PARAMETER(noslipK=.NOT.freeslipK)
38     c LOGICAL freeslip1,noslip1
39     c PARAMETER(freeslip1=.TRUE.)
40     c PARAMETER(noslip1=.NOT.freeslip1)
41 adcroft 1.2 c1 _RL wBarYZ,vZbarZ
42    
43     Kp1=min(K+1,Nr)
44     mask_Kp1=1.
45     IF (K.EQ.Nr) mask_Kp1=0.
46     Km1=max(K-1,1)
47     mask_Km1=1.
48     IF (K.EQ.1) mask_Km1=0.
49    
50 jmc 1.3 DO J=2-Oly,sNy+Oly
51     DO I=1-Olx,sNx+Olx
52 adcroft 1.2
53 jmc 1.3 c vmask_K=_maskS(i,j,k,bi,bj)
54 adcroft 1.2
55     C barZ( barY( W ) )
56     c wBarYm=0.5*(wFld(I,J,K,bi,bj)+wFld(I,J-1,K,bi,bj))
57     c wBarYp=0.5*(wFld(I,J,Kp1,bi,bj)+wFld(I,J-1,Kp1,bi,bj))
58     c & *mask_Kp1
59    
60     C Transport at interface k
61 jmc 1.4 wBarYm=0.5*(
62     & wFld(I,J,K,bi,bj)*rA(i,j,bi,bj)*maskC(i,j,Km1,bi,bj)
63     & +wFld(I,J-1,K,bi,bj)*rA(i,j-1,bi,bj)*maskC(i,j-1,Km1,bi,bj)
64     & )*mask_Km1
65    
66     C Transport at interface k+1 (here wFld is already masked)
67     wBarYp=0.5*(
68     & wFld(I,J,Kp1,bi,bj)*rA(i,j,bi,bj)
69     & +wFld(I,J-1,Kp1,bi,bj)*rA(i,j-1,bi,bj)
70     & )*mask_Kp1
71 adcroft 1.2
72     C delta_Z( V ) @ interface k
73 jmc 1.4 c vmask_Km1=mask_Km1*maskS(i,j,Km1,bi,bj)
74 adcroft 1.2 vZm=(mask_Km1*vFld(I,J,Km1,bi,bj)-vFld(I,J,K,bi,bj))
75 jmc 1.6 c & *rkFac
76 adcroft 1.2 c2 & *recip_dRC(K)
77 jmc 1.4 c IF (freeslip1) vZm=vZm*vmask_Km1
78     c IF (noslip1.AND.vmask_Km1.EQ.0.) vZm=vZm*2.
79 adcroft 1.2
80     C delta_Z( V ) @ interface k+1
81 jmc 1.4 c vmask_Kp1=mask_Kp1*maskS(i,j,Kp1,bi,bj)
82 adcroft 1.2 vZp=(vFld(I,J,K,bi,bj)-mask_Kp1*vFld(I,J,Kp1,bi,bj))
83 jmc 1.6 c & *rkFac
84 adcroft 1.2 c2 & *recip_dRC(Kp1)
85 jmc 1.4 c IF (freeslipK) vZp=vZp*vmask_Kp1
86     c IF (noslipK.AND.vmask_Kp1.EQ.0.) vZp=vZp*2.
87 adcroft 1.2
88     c1 IF (upwindShear) THEN
89     c1 wBarYZ=0.5*( wBarXm + wBarXp )
90     c1 IF (wBarYZ.GT.0.) THEN
91     c1 vZbarZ=vZp
92     c1 ELSE
93     c1 vZbarZ=vZm
94     c1 ENDIF
95     c1 ELSE
96     c1 vZbarZ=0.5*(vZm+vZp)
97     c1 ENDIF
98     c1 vShearTerm(I,J)=-wBarYZ*vZbarZ*_maskS(I,J,K,bi,bj)
99    
100     c2 vShearTerm(I,J)=-0.5*(wBarYp*vZp+wBarYm*vZm)
101     c2 & *_maskS(I,J,K,bi,bj)
102 jmc 1.6 IF (upwindShear) THEN
103     vShearTerm(I,J)=-0.5*
104     & ( (wBarYp*vZp+wBarYm*vZm)
105     & +(ABS(wBarYp)*vZp-ABS(wBarYm)*vZm)
106     & )*recip_rAs(i,j,bi,bj)
107     & *recip_hFacS(i,j,k,bi,bj)
108     & *recip_drF(K)
109     ELSE
110     vShearTerm(I,J)=-0.5*(wBarYp*vZp+wBarYm*vZm)
111     & *recip_rAs(i,j,bi,bj)
112     & *recip_hFacS(i,j,k,bi,bj)
113     & *recip_drF(K)
114     ENDIF
115 adcroft 1.2 ENDDO
116     ENDDO
117    
118     RETURN
119     END

  ViewVC Help
Powered by ViewVC 1.1.22