/[MITgcm]/MITgcm/pkg/mom_common/mom_v_sidedrag.F
ViewVC logotype

Contents of /MITgcm/pkg/mom_common/mom_v_sidedrag.F

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


Revision 1.11 - (show annotations) (download)
Wed Oct 12 21:07:01 2005 UTC (18 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58e_post, checkpoint57y_post, checkpoint57y_pre, checkpoint57v_post, checkpoint58, checkpoint58f_post, checkpoint57x_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint58a_post, checkpoint58g_post, checkpoint57z_post, checkpoint58b_post
Changes since 1.10: +24 -22 lines
use "new" version with viscosity from mom_calc_visc and sideDragFactor.
 (allows to return to the "old" version by setting sideDragFactor=0.)

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_common/mom_v_sidedrag.F,v 1.10 2005/09/30 00:11:34 jmc Exp $
2 C $Name: $
3
4 #include "MOM_COMMON_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MOM_V_SIDEDRAG
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE MOM_V_SIDEDRAG(
11 I bi,bj,k,
12 I vFld, del2v, hFacZ,
13 I viscAh_Z,viscA4_Z,
14 I harmonic,biharmonic,useVariableViscosity,
15 O vDragTerms,
16 I myThid)
17
18 C !DESCRIPTION:
19 C Calculates the drag terms due to the no-slip condition on viscous stresses:
20 C \begin{equation*}
21 C G^v_{drag} = - \frac{2}{\Delta x_v} (A_h v - A_4 \nabla^2 v)
22 C \end{equation*}
23
24 C !USES: ===============================================================
25 IMPLICIT NONE
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31
32 C !INPUT PARAMETERS: ===================================================
33 C bi,bj :: tile indices
34 C k :: vertical level
35 C uvld :: meridional flow
36 C del2v :: Laplacian of meridional flow
37 C hFacZ :: fractional open water at vorticity points
38 C myThid :: thread number
39 INTEGER bi,bj,k
40 _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42 _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
43 _RL viscAh_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44 _RL viscA4_Z(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45 LOGICAL harmonic,biharmonic,useVariableViscosity
46 INTEGER myThid
47
48 C !OUTPUT PARAMETERS: ==================================================
49 C vDragTerms :: drag term
50 _RL vDragTerms(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51
52 C !LOCAL VARIABLES: ====================================================
53 C i,j :: loop indices
54 C hFacZClosedE :: fractional open water to east
55 C hFacZClosedW :: fractional open water to west
56 INTEGER i,j
57 _RL hFacZClosedE,hFacZClosedW
58 CEOP
59 _RL Ahtmp,A4tmp
60
61
62 IF ( sideDragFactor.LE.0. ) THEN
63 C-- Laplacian and bi-harmonic terms: variable-Viscosity coeff. from
64 C MOM_CALC_VISC are not used here (corresponds to the "old" version).
65
66 DO j=2-Oly,sNy+Oly-1
67 DO i=2-Olx,sNx+Olx-1
68 #ifdef NONLIN_FRSURF
69 C- this will not give any side-drag along thin wall.
70 C (but this might just be what we want ...)
71 hFacZClosedW = h0FacS(i,j,k,bi,bj) - h0FacS(i-1,j,k,bi,bj)
72 hFacZClosedE = h0FacS(i,j,k,bi,bj) - h0FacS(i+1,j,k,bi,bj)
73 hFacZClosedW = MAX( 0. _d 0, hFacZClosedW )
74 hFacZClosedE = MAX( 0. _d 0, hFacZClosedE )
75 #else
76 hFacZClosedW = _hFacS(i,j,k,bi,bj) - hFacZ(i,j)
77 hFacZClosedE = _hFacS(i,j,k,bi,bj) - hFacZ(i+1,j)
78 #endif
79 Ahtmp=min(viscAh+viscAhGrid*rAs(i,j,bi,bj)/deltaTmom,
80 & viscAhMax)
81 A4tmp=min(viscA4+viscA4Grid*(rAs(i,j,bi,bj)**2)/deltaTmom,
82 & viscA4Max)
83 IF (viscA4GridMax.GT.0.) THEN
84 A4tmp=min(A4tmp,viscA4GridMax*(rAs(i,j,bi,bj)**2)/deltaTmom)
85 ENDIF
86 A4tmp=max(A4tmp,viscA4GridMin*(rAs(i,j,bi,bj)**2)/deltaTmom)
87 vDragTerms(i,j) =
88 & -_recip_hFacS(i,j,k,bi,bj)
89 & *recip_drF(k)*recip_rAs(i,j,bi,bj)
90 & *( hFacZClosedW*_dyU( i ,j,bi,bj)
91 & *_recip_dxV( i ,j,bi,bj)
92 & +hFacZClosedE*_dyU(i+1,j,bi,bj)
93 & *_recip_dxV(i+1,j,bi,bj) )
94 & *drF(k)*2.*(
95 & Ahtmp*vFld(i,j)*cosFacV(j,bi,bj)
96 #ifdef COSINEMETH_III
97 & -viscA4*del2v(i,j)*sqcosFacV(j,bi,bj)
98 #else
99 & -A4tmp*del2v(i,j)*cosFacV(j,bi,bj)
100 #endif
101 & )
102 ENDDO
103 ENDDO
104
105 ELSE
106 C-- Laplacian and bi-harmonic terms: using variable-Viscosity coeff.
107 C from MOM_CALC_VISC, consistent with dissipation in the interior
108
109 DO j=2-Oly,sNy+Oly-1
110 DO i=2-Olx,sNx+Olx-1
111 C- this will not give any side-drag along thin wall.
112 C (but this might just be what we want ...)
113 #ifdef NONLIN_FRSURF
114 hFacZClosedW = h0FacS(i,j,k,bi,bj) - h0FacS(i-1,j,k,bi,bj)
115 hFacZClosedE = h0FacS(i,j,k,bi,bj) - h0FacS(i+1,j,k,bi,bj)
116 #else
117 hFacZClosedW = hFacS(i,j,k,bi,bj) - hFacS(i-1,j,k,bi,bj)
118 hFacZClosedE = hFacS(i,j,k,bi,bj) - hFacS(i+1,j,k,bi,bj)
119 #endif
120 hFacZClosedW = MAX( 0. _d 0, hFacZClosedW )
121 hFacZClosedE = MAX( 0. _d 0, hFacZClosedE )
122 vDragTerms(i,j) =
123 & -_recip_hFacS(i,j,k,bi,bj)
124 & *recip_drF(k)*recip_rAs(i,j,bi,bj)
125 & *( hFacZClosedW*_dyU( i ,j,bi,bj)*_recip_dxV( i ,j,bi,bj)
126 & *( viscAh_Z(i ,j)*vFld(i,j)*cosFacV(j,bi,bj)
127 #ifdef COSINEMETH_III
128 & -viscA4_Z(i ,j)*del2v(i,j)*sqcosFacV(j,bi,bj) )
129 #else
130 & -viscA4_Z(i ,j)*del2v(i,j)*cosFacV(j,bi,bj) )
131 #endif
132 & +hFacZClosedE*_dyU(i+1,j,bi,bj)*_recip_dxV(i+1,j,bi,bj)
133 & *( viscAh_Z(i+1,j)*vFld(i,j)*cosFacV(j,bi,bj)
134 #ifdef COSINEMETH_III
135 & -viscA4_Z(i+1,j)*del2v(i,j)*sqcosFacV(j,bi,bj) )
136 #else
137 & -viscA4_Z(i+1,j)*del2v(i,j)*cosFacV(j,bi,bj) )
138 #endif
139 & )*drF(k)*sideDragFactor
140 ENDDO
141 ENDDO
142
143 C-- end old-version / new-version IF blocks
144 ENDIF
145
146 #ifdef ALLOW_DIAGNOSTICS
147 IF (useDiagnostics) THEN
148 CALL DIAGNOSTICS_FILL(vDragTerms,'VSidDrag',k,1,2,bi,bj,myThid)
149 ENDIF
150 #endif /* ALLOW_DIAGNOSTICS */
151
152 RETURN
153 END

  ViewVC Help
Powered by ViewVC 1.1.22