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

Annotation of /MITgcm/pkg/generic_advdiff/gad_dst3_adv_x.F

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


Revision 1.11 - (hide annotations) (download)
Tue Dec 5 22:21:50 2006 UTC (17 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint58t_post, checkpoint58w_post, mitgcm_mapl_00, checkpoint58v_post, checkpoint58x_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.10: +7 -8 lines
change horizontal CFL for deep-model.

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

  ViewVC Help
Powered by ViewVC 1.1.22