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

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

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


Revision 1.11 - (show annotations) (download)
Wed Jul 4 20:22:26 2012 UTC (11 years, 10 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint64, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint65o, 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, HEAD
Changes since 1.10: +7 -7 lines
comment out test on inAdMode (has no effect + OLD_DST3_FORMULATION no longer used)

1 C $Header: /u/gcmpack/MITgcm/pkg/generic_advdiff/gad_dst3_adv_r.F,v 1.10 2011/03/29 15:47:19 jmc Exp $
2 C $Name: $
3
4 #include "GAD_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: GAD_DST3_ADV_R
8
9 C !INTERFACE: ==========================================================
10 SUBROUTINE GAD_DST3_ADV_R(
11 I bi,bj,k,dTarg,
12 I rTrans, wFld,
13 I tracer,
14 O wT,
15 I myThid )
16
17 C !DESCRIPTION:
18 C Calculates the area integrated vertical flux due to advection of a tracer
19 C using 3rd-order Direct Space and Time (DST-3) Advection Scheme
20
21 C !USES: ===============================================================
22 IMPLICIT NONE
23
24 C == GLobal variables ==
25 #include "SIZE.h"
26 #ifdef OLD_DST3_FORMULATION
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #endif
30 #include "GRID.h"
31 #include "GAD.h"
32
33 C == Routine arguments ==
34 C !INPUT PARAMETERS: ===================================================
35 C bi,bj :: tile indices
36 C k :: vertical level
37 C deltaTloc :: local time-step (s)
38 C rTrans :: vertical volume transport
39 C wFld :: vertical flow
40 C tracer :: tracer field
41 C myThid :: thread number
42 INTEGER bi,bj,k
43 _RL dTarg
44 _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45 _RL wFld (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46 _RL tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
47 INTEGER myThid
48
49 C !OUTPUT PARAMETERS: ==================================================
50 C wT :: vertical advective flux
51 _RL wT (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52
53 C == Local variables ==
54 C !LOCAL VARIABLES: ====================================================
55 C i,j :: loop indices
56 C km1 :: =max( k-1 , 1 )
57 C wLoc :: velocity, vertical component
58 C wCFL :: Courant-Friedrich-Levy number
59 INTEGER i,j,kp1,km1,km2
60 _RL wLoc
61 _RL Rjm,Rj,Rjp,cfl,d0,d1
62 #ifdef OLD_DST3_FORMULATION
63 _RL psiP,psiM,thetaP,thetaM
64 _RL smallNo
65
66 c IF (inAdMode) THEN
67 c smallNo = 1.0D-20
68 c ELSE
69 smallNo = 1.0D-20
70 c ENDIF
71 #endif
72
73 km2=MAX(1,k-2)
74 km1=MAX(1,k-1)
75 kp1=MIN(Nr,k+1)
76
77 DO j=1-OLy,sNy+OLy
78 DO i=1-OLx,sNx+OLx
79 Rjp=(tracer(i,j,k)-tracer(i,j,kp1))
80 & *maskC(i,j,kp1,bi,bj)
81 Rj =(tracer(i,j,km1)-tracer(i,j,k))
82 & *maskC(i,j,k,bi,bj)*maskC(i,j,km1,bi,bj)
83 Rjm=(tracer(i,j,km2)-tracer(i,j,km1))
84 & *maskC(i,j,km1,bi,bj)
85
86 wLoc = wFld(i,j)
87 c wLoc = rTrans(i,j)*recip_rA(i,j,bi,bj)
88 cfl=ABS(wLoc*dTarg*recip_drC(k))
89 d0=(2.-cfl)*(1.-cfl)*oneSixth
90 d1=(1.-cfl*cfl)*oneSixth
91 #ifdef OLD_DST3_FORMULATION
92 IF ( ABS(Rj).LT.smallNo .OR.
93 & ABS(Rjm).LT.smallNo ) THEN
94 thetaP=0.
95 psiP=0.
96 ELSE
97 thetaP=(Rjm+smallNo)/(smallNo+Rj)
98 psiP=d0+d1*thetaP
99 ENDIF
100 IF ( ABS(Rj).LT.smallNo .OR.
101 & ABS(Rjp).LT.smallNo ) THEN
102 thetaM=0.
103 psiM=0.
104 ELSE
105 thetaM=(Rjp+smallNo)/(smallNo+Rj)
106 psiM=d0+d1*thetaM
107 ENDIF
108 wT(i,j)=
109 & 0.5*(rTrans(i,j)+ABS(rTrans(i,j)))
110 & *( tracer(i,j, k ) + psiM*Rj )
111 & +0.5*(rTrans(i,j)-ABS(rTrans(i,j)))
112 & *( tracer(i,j,km1) - psiP*Rj )
113 #else /* OLD_DST3_FORMULATION */
114 wT(i,j)=
115 & 0.5*(rTrans(i,j)+ABS(rTrans(i,j)))
116 & *( tracer(i,j, k ) + (d0*Rj+d1*Rjp) )
117 & +0.5*(rTrans(i,j)-ABS(rTrans(i,j)))
118 & *( tracer(i,j,km1) - (d0*Rj+d1*Rjm) )
119 #endif /* OLD_DST3_FORMULATION */
120
121 ENDDO
122 ENDDO
123
124 RETURN
125 END

  ViewVC Help
Powered by ViewVC 1.1.22