/[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.16 - (show annotations) (download)
Fri Jun 26 23:10:09 2009 UTC (15 years ago) by jahn
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint62, checkpoint63, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62b, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61s, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.15: +16 -3 lines
add package longstep

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_rtransport.F,v 1.15 2008/05/30 02:50:16 gforget 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,tracerIdentity,
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 #include "GAD.h"
26 #ifdef ALLOW_LONGSTEP
27 #include "LONGSTEP.h"
28 #endif
29
30 #ifdef ALLOW_AUTODIFF_TAMC
31 # include "tamc.h"
32 # include "tamc_keys.h"
33 # ifdef ALLOW_PTRACERS
34 # include "PTRACERS_SIZE.h"
35 # endif
36 #endif /* ALLOW_AUTODIFF_TAMC */
37
38 C == Routine arguments ==
39 C iMin,iMax,jMin, - Range of points for which calculation
40 C jMax,bi,bj,k results will be set.
41 C xA - Area of X face
42 C Tracer - 3D Tracer field
43 C df - Diffusive flux component work array.
44 INTEGER iMin,iMax,jMin,jMax,bi,bj,k
45 _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
46 INTEGER tracerIdentity
47 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48 INTEGER myThid
49
50 #ifdef ALLOW_GMREDI
51
52 C == Local variables ==
53 C I, J - Loop counters
54 INTEGER I, J
55 _RL dTdx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 _RL dTdy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
57 #ifdef GM_BOLUS_ADVEC
58 _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59 #endif
60
61 #ifdef ALLOW_AUTODIFF_TAMC
62 act0 = tracerIdentity - 1
63 max0 = maxpass
64 act1 = bi - myBxLo(myThid)
65 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
66 act2 = bj - myByLo(myThid)
67 max2 = myByHi(myThid) - myByLo(myThid) + 1
68 act3 = myThid - 1
69 max3 = nTx*nTy
70 act4 = ikey_dynamics - 1
71 igadkey = (act0 + 1)
72 & + act1*max0
73 & + act2*max0*max1
74 & + act3*max0*max1*max2
75 & + act4*max0*max1*max2*max3
76 kkey = (igadkey-1)*Nr + k
77 if (tracerIdentity.GT.maxpass) then
78 print *, 'ph-pass gmredi_rtrans ', maxpass, tracerIdentity
79 STOP 'maxpass seems smaller than tracerIdentity'
80 endif
81 #endif /* ALLOW_AUTODIFF_TAMC */
82
83 C Surface flux is zero
84 IF (useGMRedi .AND. K.GT.1) THEN
85
86 C- Horizontal gradients interpolated to W points
87 DO j=jMin,jMax
88 DO i=iMin,iMax
89 dTdx(i,j) = op5*(
90 & +op5*(_maskW(i+1,j,k,bi,bj)
91 & *_recip_dxC(i+1,j,bi,bj)*
92 & (Tracer(i+1,j,k,bi,bj)-Tracer(i,j,k,bi,bj))
93 & +_maskW(i,j,k,bi,bj)
94 & *_recip_dxC(i,j,bi,bj)*
95 & (Tracer(i,j,k,bi,bj)-Tracer(i-1,j,k,bi,bj)))
96 & +op5*(_maskW(i+1,j,k-1,bi,bj)
97 & *_recip_dxC(i+1,j,bi,bj)*
98 & (Tracer(i+1,j,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj))
99 & +_maskW(i,j,k-1,bi,bj)
100 & *_recip_dxC(i,j,bi,bj)*
101 & (Tracer(i,j,k-1,bi,bj)-Tracer(i-1,j,k-1,bi,bj)))
102 & )
103
104 dTdy(i,j) = op5*(
105 & +op5*(_maskS(i,j,k,bi,bj)
106 & *_recip_dyC(i,j,bi,bj)*
107 & (Tracer(i,j,k,bi,bj)-Tracer(i,j-1,k,bi,bj))
108 & +_maskS(i,j+1,k,bi,bj)
109 & *_recip_dyC(i,j+1,bi,bj)*
110 & (Tracer(i,j+1,k,bi,bj)-Tracer(i,j,k,bi,bj)))
111 & +op5*(_maskS(i,j,k-1,bi,bj)
112 & *_recip_dyC(i,j,bi,bj)*
113 & (Tracer(i,j,k-1,bi,bj)-Tracer(i,j-1,k-1,bi,bj))
114 & +_maskS(i,j+1,k-1,bi,bj)
115 & *_recip_dyC(i,j+1,bi,bj)*
116 & (Tracer(i,j+1,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj)))
117 & )
118 ENDDO
119 ENDDO
120
121 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
122 CADJ STORE dTdx(:,:) =
123 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
124 CADJ STORE dTdy(:,:) =
125 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
126 #endif
127
128 C- Off-diagonal components of vertical flux
129 DO j=jMin,jMax
130 DO i=iMin,iMax
131 IF ( tracerIdentity .LT. GAD_TR1 ) THEN
132 df(i,j) = df(i,j)
133 & - _rA(i,j,bi,bj)
134 & *( Kwx(i,j,k,bi,bj)*dTdx(i,j)+Kwy(i,j,k,bi,bj)*dTdy(i,j) )
135 ELSE
136 df(i,j) = df(i,j)
137 & - _rA(i,j,bi,bj)
138 #ifdef ALLOW_LONGSTEP
139 & *(LS_Kwx(i,j,k,bi,bj)*dTdx(i,j)+LS_Kwy(i,j,k,bi,bj)*dTdy(i,j))
140 #else
141 & *( Kwx(i,j,k,bi,bj)*dTdx(i,j)+Kwy(i,j,k,bi,bj)*dTdy(i,j) )
142 #endif
143 ENDIF
144 ENDDO
145 ENDDO
146
147 #ifdef GM_BOLUS_ADVEC
148 IF (GM_AdvForm .AND. GM_AdvSeparate
149 & .AND. .NOT.GM_InMomAsStress) THEN
150 DO j=jMin,jMax
151 DO i=iMin,iMax
152 rTrans(i,j) =
153 & dyG(i+1,j,bi,bj)*GM_PsiX(i+1,j,k,bi,bj)
154 & -dyG( i ,j,bi,bj)*GM_PsiX( i ,j,k,bi,bj)
155 & +dxG(i,j+1,bi,bj)*GM_PsiY(i,j+1,k,bi,bj)
156 & -dxG(i, j ,bi,bj)*GM_PsiY(i, j ,k,bi,bj)
157 ENDDO
158 ENDDO
159 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
160 CADJ STORE rtrans(:,:) =
161 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
162 #endif
163 DO j=jMin,jMax
164 DO i=iMin,iMax
165 df(i,j) = df(i,j)
166 & +rTrans(i,j)*op5
167 & *(Tracer(i,j,k,bi,bj)+Tracer(i,j,k-1,bi,bj))
168 ENDDO
169 ENDDO
170 ENDIF
171 #endif /* GM_BOLUS_ADVEC */
172
173 c IF (.NOT.implicitDiffusion) THEN
174 c
175 c This vertical diffusion term is currently implemented
176 c by adding the VisbeckK*Kwz diffusivity to KappaRT/S
177 c See calc_diffusivity.F and calc_gt.F (calc_gs.F)
178 c
179 c DO j=jMin,jMax
180 c DO i=iMin,iMax
181 c df(i,j) = df(i,j) - _rA(i,j,bi,bj)
182 c & *maskUp(i,j)*VisbeckK(i,j,bi,bj)*Kwz(i,j,k,bi,bj)
183 c & *recip_drC(k)*rkfac
184 c & *(Tracer(i,j,k-1,bi,bj)-Tracer(i,j,k,bi,bj))
185 c ENDDO
186 c ENDDO
187 c ENDIF
188
189 ENDIF
190 #endif /* ALLOW_GMREDI */
191
192 RETURN
193 END

  ViewVC Help
Powered by ViewVC 1.1.22