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

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

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


Revision 1.9 - (show annotations) (download)
Tue May 3 19:50:30 2011 UTC (13 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint64, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64t, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.8: +7 -1 lines
OBC in momentum: mask del2v by maskInS (and del^j.v by maskInC)

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_fluxform/mom_v_del2v.F,v 1.8 2011/04/25 22:46:41 jmc Exp $
2 C $Name: $
3
4 #include "MOM_FLUXFORM_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: MOM_V_DEL2V
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE MOM_V_DEL2V(
11 I bi,bj,k,
12 I vFld, hFacZ,
13 O del2v,
14 I myThid)
15
16 C !DESCRIPTION:
17 C Calculates the Laplacian of meridional flow
18
19 C !USES: ===============================================================
20 IMPLICIT NONE
21 #include "SIZE.h"
22 #include "EEPARAMS.h"
23 #include "PARAMS.h"
24 #include "GRID.h"
25 #include "SURFACE.h"
26
27 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 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 INTEGER myThid
37 C !OUTPUT PARAMETERS: ==================================================
38 C del2v :: Laplacian
39 _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
40
41 C !LOCAL VARIABLES: ====================================================
42 C i,j :: loop indices
43 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 CEOP
48
49 C Zonal flux d/dx V
50 DO j=1-Oly+1,sNy+Oly-1
51 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 & *sqCosFacV(J,bi,bj)
58 #endif
59 c & *deepFacC(k) ! dyU scaling factor
60 c & *recip_deepFacC(k) ! recip_dxV scaling factor
61 ENDDO
62 ENDDO
63
64 C Meridional flux d/dy V
65 DO j=1-Oly,sNy+Oly-1
66 DO i=1-Olx+1,sNx+Olx-1
67 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 #if (defined (ISOTROPIC_COS_SCALING) && defined (COSINEMETH_III))
72 & *sqCosFacU(J,bi,bj)
73 #endif
74 #ifdef ALLOW_OBCS
75 & *maskInC(i,j,bi,bj)
76 #endif
77 c & *deepFacC(k) ! dxF scaling factor
78 c & *recip_deepFacC(k) ! recip_dyF scaling factor
79 ENDDO
80 ENDDO
81
82 C del^2 V
83 DO j=1-Oly+1,sNy+Oly-1
84 DO i=1-Olx+1,sNx+Olx-1
85 del2v(i,j) =
86 & recip_drF(k)*_recip_hFacS(i,j,k,bi,bj)
87 & *recip_rAs(i,j,bi,bj)*recip_deepFac2C(k)
88 & *( fZon(i+1,j) - fZon(i, j )
89 & +fMer( i ,j) - fMer(i,j-1)
90 & )*_maskS(i,j,k,bi,bj)
91 #ifdef ALLOW_OBCS
92 & *maskInS(i,j,bi,bj)
93 #endif
94 ENDDO
95 ENDDO
96
97 IF (no_slip_sides) THEN
98 C-- No-slip BCs impose a drag at walls...
99 DO j=1-Oly+1,sNy+Oly-1
100 DO i=1-Olx+1,sNx+Olx-1
101 #ifdef NONLIN_FRSURF
102 C- this will not give any side-drag along thin wall.
103 C (but this might just be what we want ...)
104 hFacZClosedW = h0FacS(i,j,k,bi,bj) - h0FacS(i-1,j,k,bi,bj)
105 hFacZClosedE = h0FacS(i,j,k,bi,bj) - h0FacS(i+1,j,k,bi,bj)
106 hFacZClosedW = MAX( 0. _d 0, hFacZClosedW )
107 hFacZClosedE = MAX( 0. _d 0, hFacZClosedE )
108 #else
109 hFacZClosedW = _hFacS(i,j,k,bi,bj) - hFacZ(i,j)
110 hFacZClosedE = _hFacS(i,j,k,bi,bj) - hFacZ(i+1,j)
111 #endif
112 del2v(i,j) = del2v(i,j)
113 & -_recip_hFacS(i,j,k,bi,bj)
114 & *recip_rAs(i,j,bi,bj)*recip_deepFac2C(k)
115 & *( hFacZClosedW*dyU( i ,j,bi,bj)
116 & *_recip_dxV( i ,j,bi,bj)
117 & +hFacZClosedE*dyU(i+1,j,bi,bj)
118 & *_recip_dxV(i+1,j,bi,bj)
119 & )*vFld(i,j)*sideDragFactor
120 & *_maskS(i,j,k,bi,bj)
121 ENDDO
122 ENDDO
123 ENDIF
124
125 RETURN
126 END

  ViewVC Help
Powered by ViewVC 1.1.22