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

Annotation of /MITgcm/pkg/mom_fluxform/mom_v_del2v.F

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


Revision 1.8 - (hide annotations) (download)
Mon Apr 25 22:46:41 2011 UTC (13 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62w
Changes since 1.7: +25 -15 lines
side-drag part:
 - use parameter "sideDragFactor" (instead of factor 2)
 - fix for rStar coordinate (or surface level with z-coord & Non-Lin FS)

1 jmc 1.8 C $Header: /u/gcmpack/MITgcm/pkg/mom_fluxform/mom_v_del2v.F,v 1.7 2006/12/05 05:30:38 jmc Exp $
2 adcroft 1.3 C $Name: $
3 adcroft 1.2
4 edhill 1.5 #include "MOM_FLUXFORM_OPTIONS.h"
5 adcroft 1.2
6 adcroft 1.3 CBOP
7     C !ROUTINE: MOM_V_DEL2V
8    
9     C !INTERFACE: ==========================================================
10 adcroft 1.2 SUBROUTINE MOM_V_DEL2V(
11     I bi,bj,k,
12     I vFld, hFacZ,
13     O del2v,
14     I myThid)
15 adcroft 1.3
16     C !DESCRIPTION:
17     C Calculates the Laplacian of meridional flow
18    
19     C !USES: ===============================================================
20 adcroft 1.2 IMPLICIT NONE
21     #include "SIZE.h"
22     #include "EEPARAMS.h"
23     #include "PARAMS.h"
24     #include "GRID.h"
25 jmc 1.8 #include "SURFACE.h"
26 adcroft 1.2
27 adcroft 1.3 C !INPUT PARAMETERS: ===================================================
28     C bi,bj :: tile indices
29     C k :: vertical level
30     C vFld :: meridional flow
31     C hFacZ :: fractional thickness at vorticity points
32     C myThid :: thread number`
33 adcroft 1.2 INTEGER bi,bj,k
34     _RL vFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
35     _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
36 adcroft 1.3 INTEGER myThid
37     C !OUTPUT PARAMETERS: ==================================================
38     C del2v :: Laplacian
39 adcroft 1.2 _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40    
41 adcroft 1.3 C !LOCAL VARIABLES: ====================================================
42     C i,j :: loop indices
43 adcroft 1.2 INTEGER I,J
44     _RL fZon(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45     _RL fMer(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46     _RS hFacZClosedE,hFacZClosedW
47 adcroft 1.3 CEOP
48 adcroft 1.2
49     C Zonal flux d/dx V
50 jmc 1.4 DO j=1-Oly+1,sNy+Oly-1
51 adcroft 1.2 DO i=1-Olx+1,sNx+Olx
52     fZon(i,j) = drF(k)*hFacZ(i,j)
53     & *_dyU(i,j,bi,bj)
54     & *_recip_dxV(i,j,bi,bj)
55     & *(vFld(i,j)-vFld(i-1,j))
56     #ifdef COSINEMETH_III
57 jmc 1.7 & *sqCosFacV(J,bi,bj)
58 adcroft 1.2 #endif
59 jmc 1.7 c & *deepFacC(k) ! dyU scaling factor
60     c & *recip_deepFacC(k) ! recip_dxV scaling factor
61 adcroft 1.2 ENDDO
62     ENDDO
63    
64     C Meridional flux d/dy V
65     DO j=1-Oly,sNy+Oly-1
66 jmc 1.4 DO i=1-Olx+1,sNx+Olx-1
67 adcroft 1.2 fMer(i,j) = drF(k)*_hFacC(i,j,k,bi,bj)
68     & *_dxF(i,j,bi,bj)
69     & *_recip_dyF(i,j,bi,bj)
70     & *(vFld(i,j+1)-vFld(i,j))
71 mlosch 1.6 #if (defined (ISOTROPIC_COS_SCALING) && defined (COSINEMETH_III))
72 jmc 1.7 & *sqCosFacU(J,bi,bj)
73 mlosch 1.6 #endif
74 jmc 1.7 c & *deepFacC(k) ! dxF scaling factor
75     c & *recip_deepFacC(k) ! recip_dyF scaling factor
76 adcroft 1.2 ENDDO
77     ENDDO
78    
79 jmc 1.4 C del^2 V
80     DO j=1-Oly+1,sNy+Oly-1
81     DO i=1-Olx+1,sNx+Olx-1
82 jmc 1.7 del2v(i,j) =
83     & recip_drF(k)*_recip_hFacS(i,j,k,bi,bj)
84     & *recip_rAs(i,j,bi,bj)*recip_deepFac2C(k)
85 adcroft 1.2 & *( fZon(i+1,j) - fZon(i, j )
86     & +fMer( i ,j) - fMer(i,j-1)
87     & )*_maskS(i,j,k,bi,bj)
88     ENDDO
89     ENDDO
90    
91     IF (no_slip_sides) THEN
92     C-- No-slip BCs impose a drag at walls...
93 jmc 1.8 DO j=1-Oly+1,sNy+Oly-1
94     DO i=1-Olx+1,sNx+Olx-1
95     #ifdef NONLIN_FRSURF
96     C- this will not give any side-drag along thin wall.
97     C (but this might just be what we want ...)
98     hFacZClosedW = h0FacS(i,j,k,bi,bj) - h0FacS(i-1,j,k,bi,bj)
99     hFacZClosedE = h0FacS(i,j,k,bi,bj) - h0FacS(i+1,j,k,bi,bj)
100     hFacZClosedW = MAX( 0. _d 0, hFacZClosedW )
101     hFacZClosedE = MAX( 0. _d 0, hFacZClosedE )
102     #else
103     hFacZClosedW = _hFacS(i,j,k,bi,bj) - hFacZ(i,j)
104     hFacZClosedE = _hFacS(i,j,k,bi,bj) - hFacZ(i+1,j)
105     #endif
106     del2v(i,j) = del2v(i,j)
107     & -_recip_hFacS(i,j,k,bi,bj)
108     & *recip_rAs(i,j,bi,bj)*recip_deepFac2C(k)
109     & *( hFacZClosedW*dyU( i ,j,bi,bj)
110     & *_recip_dxV( i ,j,bi,bj)
111     & +hFacZClosedE*dyU(i+1,j,bi,bj)
112     & *_recip_dxV(i+1,j,bi,bj)
113     & )*vFld(i,j)*sideDragFactor
114     & *_maskS(i,j,k,bi,bj)
115     ENDDO
116 adcroft 1.2 ENDDO
117     ENDIF
118    
119     RETURN
120     END

  ViewVC Help
Powered by ViewVC 1.1.22