/[MITgcm]/MITgcm/pkg/generic_advdiff/gad_os7mp_adv_y.F
ViewVC logotype

Contents of /MITgcm/pkg/generic_advdiff/gad_os7mp_adv_y.F

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


Revision 1.2 - (show annotations) (download)
Sun Jan 21 17:25:31 2007 UTC (17 years, 4 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58w_post, checkpoint58x_post, checkpoint58v_post
Changes since 1.1: +13 -9 lines
add a few " _d 0" to make the xlf compile swallow the new code

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_os7mp_adv_y.F,v 1.1 2007/01/20 21:20:11 adcroft Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 SUBROUTINE GAD_OS7MP_ADV_Y(
7 I bi,bj,k,deltaTloc,
8 I vTrans, vFld,
9 I maskLocS, Q,
10 O vT,
11 I myThid )
12 C /==========================================================\
13 C | SUBROUTINE GAD_OS7MP_ADV_Y |
14 C | o Compute Meridional advective Flux of tracer Q using |
15 C | 7th Order DST Sceheme with monotone preserving limiter |
16 C |==========================================================|
17 IMPLICIT NONE
18
19 C == GLobal variables ==
20 #include "SIZE.h"
21 #include "GRID.h"
22 #include "GAD.h"
23
24 C == Routine arguments ==
25 INTEGER bi,bj,k
26 _RL deltaTloc
27 _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
28 _RL vFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
29 _RS maskLocS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
30 _RL Q (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
31 _RL vT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
32 INTEGER myThid
33
34 C == Local variables ==
35 INTEGER i,j
36 _RL cfl,Psi
37 _RL vLoc,Fac,Del,DelIp,DelI,Phi,Eps,rp1h,Msk
38 _RL Qippp,Qipp,Qip,Qi,Qim,Qimm,Qimmm
39 _RL MskIpp,MskIp,MskI,MskIm,MskImm,MskImmm
40 _RL d2,d2p1,d2m1,A,B,C,D
41 _RL dp1h,dm1h,qMD,qUL,qLC,PhiMD,PhiLC,PhiMin,PhiMax
42
43 Eps = 1. _d -20
44
45 DO i=1-Olx,sNx+Olx
46 vT(i,1-Oly)=0. _d 0
47 vT(i,2-Oly)=0. _d 0
48 vT(i,3-Oly)=0. _d 0
49 vT(i,4-Oly)=0. _d 0
50 vT(i,sNy+Oly-2)=0. _d 0
51 vT(i,sNy+Oly-1)=0. _d 0
52 vT(i,sNy+Oly)=0. _d 0
53 ENDDO
54 DO j=1-Oly+4,sNy+Oly-3
55 DO i=1-Olx,sNx+Olx
56
57 vLoc = vFld(i,j)
58 cfl = abs(vLoc*deltaTloc*recip_dyC(i,j,bi,bj))
59
60 IF (vLoc.gt.0.) THEN
61 Qippp = Q(i,j+2)
62 Qipp = Q(i,j+1)
63 Qip = Q(i,j)
64 Qi = Q(i,j-1)
65 Qim = Q(i,j-2)
66 Qimm = Q(i,j-3)
67 Qimmm = Q(i,j-4)
68
69 MskIpp = maskLocS(i,j+2)
70 MskIp = maskLocS(i,j+1)
71 MskI = maskLocS(i,j)
72 MskIm = maskLocS(i,j-1)
73 MskImm = maskLocS(i,j-2)
74 MskImmm = maskLocS(i,j-3)
75 ELSEIF (vLoc.lt.0.) THEN
76 Qippp = Q(i,j-3)
77 Qipp = Q(i,j-2)
78 Qip = Q(i,j-1)
79 Qi = Q(i,j)
80 Qim = Q(i,j+1)
81 Qimm = Q(i,j+2)
82 Qimmm = Q(i,j+3)
83
84 MskIpp = maskLocS(i,j-2)
85 MskIp = maskLocS(i,j-1)
86 MskI = maskLocS(i,j)
87 MskIm = maskLocS(i,j+1)
88 MskImm = maskLocS(i,j+2)
89 MskImmm = maskLocS(i,j+3)
90 ENDIF
91
92 IF (vLoc.ne.0.) THEN
93 C 2nd order correction [i i-1]
94 Fac = 1.
95 Del = Qip-Qi
96 Msk = MskI
97 Phi = Msk * Fac * Del
98 C 3rd order correction [i i-1 i-2]
99 Fac = Fac * ( cfl + 1. )/3.
100 Del = Del - ( Qi-Qim )
101 Msk = Msk * MskIm
102 Phi = Phi - Msk * Fac * Del
103 C 4th order correction [i+1 i i-1 i-2]
104 Fac = Fac * ( cfl - 2. )/4.
105 Del = ( Qipp-2.*Qip+Qi ) - Del
106 Msk = Msk * MskIp
107 Phi = Phi + Msk * Fac * Del
108 C 5th order correction [i+1 i i-1 i-2 i-3]
109 Fac = Fac * ( cfl - 3. )/5.
110 Del = Del - ( Qip-3.*Qi+3.*Qim-Qimm )
111 Msk = Msk * MskImm
112 Phi = Phi + Msk * Fac * Del
113 C 6th order correction [i+2 i+1 i i-1 i-2 i-3]
114 Fac = Fac * ( cfl + 2. )/6.
115 Del = ( Qippp-4.*Qipp+6.*Qip-4.*Qi+Qim ) - Del
116 Msk = Msk * MskIpp
117 Phi = Phi + Msk * Fac * Del
118 C 7th order correction [i+2 i+1 i i-1 i-2 i-3 i-4]
119 Fac = Fac * ( cfl + 2. )/7.
120 Del = Del - ( Qipp-5.*Qip+10.*Qi-10.*Qim+5.*Qimm-Qimmm )
121 Msk = Msk * MskImmm
122 Phi = Phi - Msk * Fac * Del
123
124 DelIp = ( Qip - Qi ) * MskI
125 Phi = sign(1. _d 0,Phi)*sign(1. _d 0,DelIp)
126 & *abs(Phi+Eps)/abs(DelIp+Eps)
127
128 DelI = ( Qi - Qim ) * MskIm
129 rp1h =sign(1. _d 0,DelI)*sign(1. _d 0,DelIp)
130 & *abs(DelI+Eps)/abs(DelIp+Eps)
131
132 C TVD limiter
133 ! Phi = max(0. _d 0, min( 2./(1-cfl), Phi, 2.*rp1h/cfl ) )
134
135 C MP limiter
136 d2 = ( ( Qip + Qim ) - 2.*Qi ) * MskI * MskIm
137 d2p1 = ( ( Qipp + Qi ) - 2.*Qip ) * MskIp * MskI
138 d2m1 = ( ( Qi + Qimm ) - 2.*Qim ) * MskIm * MskImm
139 A = 4.*d2 - d2p1
140 B = 4.*d2p1 - d2
141 C = d2
142 D = d2p1;
143 dp1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)
144 A = 4.*d2m1 - d2
145 B = 4.*d2 - d2m1
146 C = d2m1
147 D = d2;
148 dm1h = max(min(A,B,C,D),0. _d 0)+min(max(A,B,C,D),0. _d 0)
149 qMD = 0.5*( ( Qi + Qip ) - dp1h )
150 qUL = Qi + (1.-cfl)/cfl*( Qi-Qim )
151 qLC = Qi + 0.5*( 1.+dm1h/(Qi-Qim+Eps) )*(qUL-Qi)
152 PhiMD = 2./(1.-cfl)*(qMD-Qi+Eps)/(Qip-Qi+Eps)
153 PhiLC = 2.*rp1h/cfl*(qLC-Qi+Eps)/(qUL-Qi+Eps)
154 PhiMin = max(min(0. _d 0,PhiMD),
155 & min(0. _d 0,2.*rp1h/cfl,PhiLC))
156 PhiMax = min(max(2. _d 0/(1.-cfl),PhiMD),
157 & max(0. _d 0,2.*rp1h/cfl,PhiLC))
158 Phi = max(PhiMin,min(Phi,PhiMax))
159
160 Psi = Phi * 0.5 * (1. - cfl)
161 vT(i,j) = vTrans(i,j)*( Qi + Psi*DelIp )
162 ELSE
163 vt(i,j) = 0.
164 ENDIF
165
166 ENDDO
167 ENDDO
168
169 RETURN
170 END

  ViewVC Help
Powered by ViewVC 1.1.22