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

Contents of /MITgcm/pkg/mom_vecinv/mom_vi_del2uv.F

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


Revision 1.16 - (show annotations) (download)
Tue May 3 19:36:11 2011 UTC (13 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63g, checkpoint64, checkpoint65, checkpoint63, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64q, checkpoint64p, checkpoint64s, checkpoint64r, checkpoint64u, checkpoint64t, checkpoint64w, checkpoint64v, checkpoint64i, checkpoint64h, checkpoint64k, checkpoint64j, checkpoint64m, checkpoint64l, checkpoint64o, checkpoint64n, checkpoint64a, checkpoint64c, checkpoint64b, checkpoint64e, checkpoint64d, checkpoint64g, checkpoint64f
Changes since 1.15: +7 -1 lines
OBC in momentum: mask del2u & del2v using maskInW & maskInS

1 C $Header: /u/gcmpack/MITgcm/pkg/mom_vecinv/mom_vi_del2uv.F,v 1.15 2011/04/25 20:14:02 jmc Exp $
2 C $Name: $
3
4 #include "MOM_VECINV_OPTIONS.h"
5
6 SUBROUTINE MOM_VI_DEL2UV(
7 I bi,bj,k,
8 I hDiv,vort3,hFacZ,
9 O del2u,del2v,
10 I myThid)
11 IMPLICIT NONE
12 C
13 C Calculate del^2 of (u,v) in terms of hDiv and vort3
14 C
15
16 C == Global variables ==
17 #include "SIZE.h"
18 #include "GRID.h"
19 #include "EEPARAMS.h"
20
21 C == Routine arguments ==
22 INTEGER bi,bj,k
23 _RL hDiv(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
24 _RL vort3(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
25 _RS hFacZ(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
26 _RL del2u(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
27 _RL del2v(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
28 INTEGER myThid
29
30 C == Local variables ==
31 INTEGER i,j
32 c _RL Zip,Zij,Zpj,Dim,Dij,Dmj,uDij
33
34 C - bi-harmonic viscosity :
35
36 c DO j=2-Oly,sNy+Oly-1
37 c DO i=2-Olx,sNx+Olx-1
38
39 c Dim=dyF( i ,j-1,bi,bj)*hFacC( i ,j-1,k,bi,bj)*hDiv( i ,j-1)
40 c Dij=dyF( i , j ,bi,bj)*hFacC( i , j ,k,bi,bj)*hDiv( i , j )
41 c Dmj=dyF(i-1, j ,bi,bj)*hFacC(i-1, j ,k,bi,bj)*hDiv(i-1, j )
42 c Dim=dyF( i ,j-1,bi,bj)* hDiv( i ,j-1)
43 c Dij=dyF( i , j ,bi,bj)* hDiv( i , j )
44 c Dmj=dyF(i-1, j ,bi,bj)* hDiv(i-1, j )
45 c Dim= hDiv( i ,j-1)
46 c Dij= hDiv( i , j )
47 c Dmj= hDiv(i-1, j )
48
49 c Zip=dxV( i ,j+1,bi,bj)*hFacZ( i ,j+1)*vort3( i ,j+1)
50 c Zij=dxV( i , j ,bi,bj)*hFacZ( i , j )*vort3( i , j )
51 c Zpj=dxV(i+1, j ,bi,bj)*hFacZ(i+1, j )*vort3(i+1, j )
52 c Zip= hFacZ( i ,j+1)*vort3( i ,j+1)
53 c Zij= hFacZ( i , j )*vort3( i , j )
54 c Zpj= hFacZ(i+1, j )*vort3(i+1, j )
55
56
57 c del2u(i,j) = recip_rAw(i,j,bi,bj)*(
58 c & +recip_hFacW(i,j,k,bi,bj)*( Dij-Dmj )
59 c & -recip_hFacW(i,j,k,bi,bj)*( Zip-Zij ) )
60 c del2u(i,j) = recip_rAw(i,j,bi,bj)*(
61 c & + ( Dij-Dmj )
62 c & -recip_hFacW(i,j,k,bi,bj)*( Zip-Zij ) )
63 c del2u(i,j) =
64 c & + ( Dij-Dmj )*recip_DXC(i,j,bi,bj)
65 c & -recip_hFacW(i,j,k,bi,bj)*( Zip-Zij )*recip_DYG(i,j,bi,bj)
66
67 c del2v(i,j) = recip_rAs(i,j,bi,bj)*(
68 c & recip_hFacS(i,j,k,bi,bj)*( Zpj-Zij )
69 c & +recip_hFacS(i,j,k,bi,bj)*( Dij-Dim ) )
70 c del2v(i,j) = recip_rAs(i,j,bi,bj)*(
71 c & recip_hFacS(i,j,k,bi,bj)*( Zpj-Zij )
72 c & + ( Dij-Dim ) )
73 c del2v(i,j) =
74 c & recip_hFacS(i,j,k,bi,bj)*( Zpj-Zij )*recip_DXG(i,j,bi,bj)
75 c & + ( Dij-Dim )*recip_DYC(i,j,bi,bj)
76
77 c ENDDO
78 c ENDDO
79
80 C - bi-harmonic viscosity : del^2(U_component)
81
82 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
83 IF (useCubedSphereExchange) THEN
84 C to compute d/dx(hDiv), fill corners with appropriate values:
85 CALL FILL_CS_CORNER_TR_RL( 1, .FALSE.,
86 & hDiv, bi,bj, myThid )
87 ENDIF
88 cph-exch2#endif
89 c DO j=1,sNy
90 c DO i=1,sNx+1
91 DO j=2-Oly,sNy+Oly-1
92 DO i=2-Olx,sNx+Olx-1
93 del2u(i,j) =
94 & ( ( hDiv(i,j) - hDiv(i-1,j) )*recip_dxC(i,j,bi,bj)
95 & -_recip_hFacW(i,j,k,bi,bj)*
96 & ( hFacZ(i,j+1)*vort3(i,j+1) - hFacZ(i,j)*vort3(i,j) )
97 & *recip_dyG(i,j,bi,bj)
98 & )*maskW(i,j,k,bi,bj)
99 #ifdef ALLOW_OBCS
100 & *maskInW(i,j,bi,bj)
101 #endif
102 ENDDO
103 ENDDO
104
105 C - bi-harmonic viscosity : del^2(V_component)
106
107 cph-exch2#ifndef ALLOW_AUTODIFF_TAMC
108 IF (useCubedSphereExchange) THEN
109 C to compute d/dy(hDiv), fill corners with appropriate values:
110 CALL FILL_CS_CORNER_TR_RL( 2, .FALSE.,
111 & hDiv, bi,bj, myThid )
112 ENDIF
113 cph-exch2#endif
114 c DO j=1,sNy+1
115 c DO i=1,sNx
116 DO j=2-Oly,sNy+Oly-1
117 DO i=2-Olx,sNx+Olx-1
118 del2v(i,j) =
119 & ( ( hDiv(i,j) - hDiv(i,j-1) )*recip_dyC(i,j,bi,bj)
120 & +_recip_hFacS(i,j,k,bi,bj)*
121 & ( hFacZ(i+1,j)*vort3(i+1,j) - hFacZ(i,j)*vort3(i,j) )
122 & *recip_dxG(i,j,bi,bj)
123 & )*maskS(i,j,k,bi,bj)
124 #ifdef ALLOW_OBCS
125 & *maskInS(i,j,bi,bj)
126 #endif
127 ENDDO
128 ENDDO
129
130 RETURN
131 END

  ViewVC Help
Powered by ViewVC 1.1.22