/[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.19 - (show annotations) (download)
Sat Apr 26 19:47:46 2014 UTC (10 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65b, checkpoint65a, checkpoint65, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64w
Changes since 1.18: +8 -3 lines
move additional anomaly fields of control vars (related to options:
ALLOW_KAPGM_CONTROL, ALLOW_KAPREDI_CONTROL and ALLOW_BOTTOMDRAG_CONTROL)
from DYNVARS.h into new header file: CTRL_FIELDS.h

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

  ViewVC Help
Powered by ViewVC 1.1.22