/[MITgcm]/MITgcm/pkg/gmredi/gmredi_rtransport.F
ViewVC logotype

Contents of /MITgcm/pkg/gmredi/gmredi_rtransport.F

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


Revision 1.7 - (show annotations) (download)
Wed Mar 6 01:56:27 2002 UTC (22 years, 3 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint46l_post, checkpoint46g_pre, checkpoint46f_post, checkpoint46b_post, checkpoint46l_pre, checkpoint46d_pre, checkpoint45d_post, checkpoint46j_pre, checkpoint44h_pre, checkpoint46a_post, checkpoint46j_post, checkpoint46k_post, checkpoint45a_post, checkpoint46e_pre, checkpoint45b_post, checkpoint46b_pre, checkpoint46c_pre, checkpoint46, checkpoint46h_pre, checkpoint46m_post, checkpoint46a_pre, checkpoint45c_post, checkpoint44h_post, checkpoint46g_post, checkpoint46i_post, checkpoint46c_post, checkpoint46e_post, checkpoint45, checkpoint46h_post, checkpoint46d_post
Changes since 1.6: +2 -2 lines
o GM Advective form:
 Tracers are advected using the residual transport (= Eulerian + GM-bolus).
 parameter GM_AdvSeparate=T return to previous form (i.e. compute separately
  Eulerian and Bolus advection fluxes)

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_rtransport.F,v 1.6 2001/12/16 18:54:49 jmc Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 subroutine GMREDI_RTRANSPORT(
7 I iMin,iMax,jMin,jMax,bi,bj,K,
8 I Tracer,
9 U df,
10 I myThid)
11 C /==========================================================\
12 C | o SUBROUTINE GMREDI_RTRANSPORT |
13 C | Add vertical transport terms from GM/Redi |
14 C | parameterization. |
15 C |==========================================================|
16 C \==========================================================/
17 IMPLICIT NONE
18
19 C == GLobal variables ==
20 #include "SIZE.h"
21 #include "EEPARAMS.h"
22 #include "PARAMS.h"
23 #include "GRID.h"
24 #include "GMREDI.h"
25
26 C == Routine arguments ==
27 C iMin,iMax,jMin, - Range of points for which calculation
28 C jMax,bi,bj,k results will be set.
29 C xA - Area of X face
30 C Tracer - 3D Tracer field
31 C df - Diffusive flux component work array.
32 INTEGER iMin,iMax,jMin,jMax,bi,bj,k
33 _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
34 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
35 INTEGER myThid
36
37 #ifdef ALLOW_GMREDI
38
39 C == Local variables ==
40 C I, J - Loop counters
41 INTEGER I, J
42 _RL dTdx,dTdy
43 _RL rTrans
44
45 C Surface flux is zero
46 IF (useGMRedi .AND. K.GT.1) THEN
47
48 DO j=jMin,jMax
49 DO i=iMin,iMax
50
51 C- Horizontal gradients interpolated to W points
52 dTdx = 0.5*(
53 & +0.5*(_maskW(i+1,j,k,bi,bj)
54 & *_recip_dxC(i+1,j,bi,bj)*
55 & (Tracer(i+1,j,k,bi,bj)-Tracer(i,j,k,bi,bj))
56 & +_maskW(i,j,k,bi,bj)
57 & *_recip_dxC(i,j,bi,bj)*
58 & (Tracer(i,j,k,bi,bj)-Tracer(i-1,j,k,bi,bj)))
59 & +0.5*(_maskW(i+1,j,k-1,bi,bj)
60 & *_recip_dxC(i+1,j,bi,bj)*
61 & (Tracer(i+1,j,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj))
62 & +_maskW(i,j,k-1,bi,bj)
63 & *_recip_dxC(i,j,bi,bj)*
64 & (Tracer(i,j,k-1,bi,bj)-Tracer(i-1,j,k-1,bi,bj)))
65 & )
66
67 dTdy = 0.5*(
68 & +0.5*(_maskS(i,j,k,bi,bj)
69 & *_recip_dyC(i,j,bi,bj)*
70 & (Tracer(i,j,k,bi,bj)-Tracer(i,j-1,k,bi,bj))
71 & +_maskS(i,j+1,k,bi,bj)
72 & *_recip_dyC(i,j+1,bi,bj)*
73 & (Tracer(i,j+1,k,bi,bj)-Tracer(i,j,k,bi,bj)))
74 & +0.5*(_maskS(i,j,k-1,bi,bj)
75 & *_recip_dyC(i,j,bi,bj)*
76 & (Tracer(i,j,k-1,bi,bj)-Tracer(i,j-1,k-1,bi,bj))
77 & +_maskS(i,j+1,k-1,bi,bj)
78 & *_recip_dyC(i,j+1,bi,bj)*
79 & (Tracer(i,j+1,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj)))
80 & )
81
82 C- Off-diagonal components of vertical flux
83 df(i,j) = df(i,j)
84 & - _rA(i,j,bi,bj)
85 & *( Kwx(i,j,k,bi,bj)*dTdx +Kwy(i,j,k,bi,bj)*dTdy )
86
87 ENDDO
88 ENDDO
89
90 #ifdef GM_BOLUS_ADVEC
91 IF (GM_AdvForm .AND. GM_AdvSeparate) THEN
92 DO j=jMin,jMax
93 DO i=iMin,iMax
94 rTrans =
95 & dyG(i+1,j,bi,bj)*GM_PsiX(i+1,j,k,bi,bj)
96 & -dyG( i ,j,bi,bj)*GM_PsiX( i ,j,k,bi,bj)
97 & +dxG(i,j+1,bi,bj)*GM_PsiY(i,j+1,k,bi,bj)
98 & -dxG(i, j ,bi,bj)*GM_PsiY(i, j ,k,bi,bj)
99 df(i,j) = df(i,j)
100 & +rTrans*0.5
101 & *(Tracer(i,j,k,bi,bj)+Tracer(i,j,k-1,bi,bj))
102 ENDDO
103 ENDDO
104 ENDIF
105 #endif /* GM_BOLUS_ADVEC */
106
107 c IF (.NOT.implicitDiffusion) THEN
108 c
109 c This vertical diffusion term is currently implemented
110 c by adding the VisbeckK*Kwz diffusivity to KappaRT/S
111 c See calc_diffusivity.F and calc_gt.F (calc_gs.F)
112 c
113 c DO j=jMin,jMax
114 c DO i=iMin,iMax
115 c df(i,j) = df(i,j) - _rA(i,j,bi,bj)
116 c & *maskUp(i,j)*VisbeckK(i,j,bi,bj)*Kwz(i,j,k,bi,bj)
117 c & *recip_drC(k)*rkfac
118 c & *(Tracer(i,j,k-1,bi,bj)-Tracer(i,j,k,bi,bj))
119 c ENDDO
120 c ENDDO
121 c ENDIF
122
123 ENDIF
124 #endif /* ALLOW_GMREDI */
125
126 RETURN
127 END

  ViewVC Help
Powered by ViewVC 1.1.22