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

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

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


Revision 1.15 - (show annotations) (download)
Tue Jan 30 15:17:52 2007 UTC (17 years, 5 months ago) by dfer
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58y_post, checkpoint58w_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59m, checkpoint59l, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint58v_post, checkpoint58x_post, checkpoint59j
Changes since 1.14: +28 -1 lines
New diagnostics: GM Bolus transport of Pot. Temperature

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_xtransport.F,v 1.14 2004/09/17 23:02:01 heimbach Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 subroutine GMREDI_XTRANSPORT(
7 I iMin,iMax,jMin,jMax,bi,bj,K,
8 I xA,Tracer,tracerIdentity,
9 U df,
10 I myThid)
11 C /==========================================================\
12 C | o SUBROUTINE GMREDI_XTRANSPORT |
13 C | Add horizontal x 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 #ifdef ALLOW_AUTODIFF_TAMC
27 # include "tamc.h"
28 # include "tamc_keys.h"
29 # ifdef ALLOW_PTRACERS
30 # include "PTRACERS_SIZE.h"
31 # endif
32 #endif /* ALLOW_AUTODIFF_TAMC */
33
34 C == Routine arguments ==
35 C iMin,iMax,jMin, - Range of points for which calculation
36 C jMax,bi,bj,k results will be set.
37 C xA - Area of X face
38 C Tracer - 3D Tracer field
39 C df - Diffusive flux component work array.
40 INTEGER iMin,iMax,jMin,jMax,bi,bj,k
41 _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42 _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
43 integer tracerIdentity
44 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
45 INTEGER myThid
46
47 #ifdef ALLOW_GMREDI
48
49 C == Local variables ==
50 C I, J - Loop counters
51 INTEGER I, J
52 INTEGER km1,kp1
53 _RL maskp1
54 #ifdef GM_EXTRA_DIAGONAL
55 _RL dTdz (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56 #endif
57 #ifdef GM_BOLUS_ADVEC
58 _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
59 #endif
60 #ifdef ALLOW_DIAGNOSTICS
61 LOGICAL DIAGNOSTICS_IS_ON
62 EXTERNAL DIAGNOSTICS_IS_ON
63 _RL tmp1k(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64 #endif
65
66 #ifdef ALLOW_AUTODIFF_TAMC
67 act0 = tracerIdentity - 1
68 max0 = maxpass
69 act1 = bi - myBxLo(myThid)
70 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
71 act2 = bj - myByLo(myThid)
72 max2 = myByHi(myThid) - myByLo(myThid) + 1
73 act3 = myThid - 1
74 max3 = nTx*nTy
75 act4 = ikey_dynamics - 1
76 igadkey = (act0 + 1)
77 & + act1*max0
78 & + act2*max0*max1
79 & + act3*max0*max1*max2
80 & + act4*max0*max1*max2*max3
81 kkey = (igadkey-1)*Nr + k
82 if (tracerIdentity.GT.maxpass) then
83 print *, 'ph-pass gmredi_xtrans ', maxpass, tracerIdentity
84 STOP 'maxpass seems smaller than tracerIdentity'
85 endif
86 #endif /* ALLOW_AUTODIFF_TAMC */
87
88 IF (useGMRedi) THEN
89
90 #ifdef ALLOW_AUTODIFF_TAMC
91 # ifdef GM_NON_UNITY_DIAGONAL
92 CADJ STORE Kux(:,:,k,bi,bj) =
93 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
94 # endif
95 # ifdef GM_EXTRA_DIAGONAL
96 CADJ STORE Kuz(:,:,k,bi,bj) =
97 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
98 # endif
99 #endif
100
101 C-- Area integrated zonal flux
102 DO j=jMin,jMax
103 DO i=iMin,iMax
104 df(i,j) = df(i,j)
105 & -xA(i,j)
106 #ifdef GM_NON_UNITY_DIAGONAL
107 & *Kux(i,j,k,bi,bj)
108 #else
109 & *(GM_isopycK
110 #ifdef GM_VISBECK_VARIABLE_K
111 & +op5*(VisbeckK(i,j,bi,bj)+VisbeckK(i-1,j,bi,bj))
112 #endif
113 & )
114 #endif /* GM_NON_UNITY_DIAGONAL */
115 & *_recip_dxC(i,j,bi,bj)
116 & *(Tracer(i,j,k,bi,bj)-Tracer(i-1,j,k,bi,bj))
117 ENDDO
118 ENDDO
119
120 #ifdef GM_EXTRA_DIAGONAL
121 IF (GM_ExtraDiag) THEN
122 km1 = MAX(k-1,1)
123 kp1 = MIN(k+1,Nr)
124
125 DO j=jMin,jMax
126 DO i=iMin,iMax
127 C- Vertical gradients interpolated to U points
128 dTdz(i,j) = op5*(
129 & +op5*recip_drC(k)*
130 & ( maskC(i-1,j,k,bi,bj)*
131 & (Tracer(i-1,j,km1,bi,bj)-Tracer(i-1,j,k,bi,bj))
132 & +maskC( i ,j,k,bi,bj)*
133 & (Tracer( i ,j,km1,bi,bj)-Tracer( i ,j,k,bi,bj))
134 & )
135 & +op5*recip_drC(kp1)*
136 & ( maskC(i-1,j,kp1,bi,bj)*
137 & (Tracer(i-1,j,k,bi,bj)-Tracer(i-1,j,kp1,bi,bj))
138 & +maskC( i ,j,kp1,bi,bj)*
139 & (Tracer( i ,j,k,bi,bj)-Tracer( i ,j,kp1,bi,bj))
140 & ) )
141
142
143 ENDDO
144 ENDDO
145 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
146 CADJ STORE dtdz(:,:) =
147 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
148 #endif
149 DO j=jMin,jMax
150 DO i=iMin,iMax
151 C- Off-diagonal components of horizontal flux
152 df(i,j) = df(i,j) - xA(i,j)*Kuz(i,j,k,bi,bj)*dTdz(i,j)
153 ENDDO
154 ENDDO
155 ENDIF
156 #endif /* GM_EXTRA_DIAGONAL */
157
158 #ifdef GM_BOLUS_ADVEC
159 IF (GM_AdvForm .AND. GM_AdvSeparate) THEN
160 kp1 = MIN(k+1,Nr)
161 maskp1 = 1.
162 IF (k.GE.Nr) maskp1 = 0.
163 DO j=jMin,jMax
164 DO i=iMin,iMax
165 uTrans(i,j) = dyG(i,j,bi,bj)*( GM_PsiX(i,j,kp1,bi,bj)*maskp1
166 & -GM_PsiX(i,j,k,bi,bj) )
167 & *maskW(i,j,k,bi,bj)
168 ENDDO
169 ENDDO
170 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
171 CADJ STORE utrans(:,:) =
172 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
173 #endif
174 DO j=jMin,jMax
175 DO i=iMin,iMax
176 df(i,j) = df(i,j)
177 & +uTrans(i,j)*op5*(Tracer(i,j,k,bi,bj)+Tracer(i-1,j,k,bi,bj))
178 ENDDO
179 ENDDO
180 ENDIF
181
182 #ifdef ALLOW_DIAGNOSTICS
183 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
184 IF ( useDiagnostics
185 & .AND. DIAGNOSTICS_IS_ON('GM_ubT ', myThid )
186 & .AND. tracerIdentity .EQ. 1) THEN
187 kp1 = MIN(k+1,Nr)
188 maskp1 = 1.
189 IF (k.GE.Nr) maskp1 = 0.
190 DO j=jMin,jMax
191 DO i=iMin,iMax
192 tmp1k(i,j) = dyG(i,j,bi,bj)*( GM_PsiX(i,j,kp1,bi,bj)*maskp1
193 & -GM_PsiX(i,j,k,bi,bj) )
194 & *maskW(i,j,k,bi,bj)
195 & *op5*(Tracer(i,j,k,bi,bj)+Tracer(i-1,j,k,bi,bj))
196 ENDDO
197 ENDDO
198 CALL DIAGNOSTICS_FILL(tmp1k,'GM_ubT ', k,1,2,bi,bj,myThid)
199
200 ENDIF
201 #endif /* ALLOW_DIAGNOSTICS */
202
203 #endif /* GM_BOLUS_ADVEC */
204
205 ENDIF
206 #endif /* ALLOW_GMREDI */
207
208 RETURN
209 END

  ViewVC Help
Powered by ViewVC 1.1.22