/[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.17 - (show annotations) (download)
Fri May 30 02:50:17 2008 UTC (15 years, 11 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint62a, checkpoint60, checkpoint61, checkpoint62, checkpoint61f, checkpoint61n, checkpoint61q, checkpoint61e, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.16: +3 -2 lines
o bridging the gap between eddy stress and GM.
  -> eddyTau is replaced with eddyPsi (eddyTau = f x rho0 x eddyPsi)
      along with a change in CPP option (now ALLOW_EDDYPSI).
  -> when using GM w/ GM_AdvForm:
      The total eddy streamfunction (Psi = eddyPsi + K x Slope)
      is applied either in the tracer Eq. or in momentum Eq.
      depending on data.gmredi (intro. GM_InMomAsStress).
  -> ALLOW_EDDYPSI_CONTROL for estimation purpose.
  The key modifications are in model/src/taueddy_external_forcing.F
  pkg/gmredi/gmredi_calc_*F pkg/gmredi/gmredi_*transport.F

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_xtransport.F,v 1.16 2008/02/02 02:35:53 gforget 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 #ifdef ALLOW_KAPREDI_CONTROL
110 & *(kapredi(i,j,k,bi,bj)
111 #else
112 & *(GM_isopycK
113 #endif
114 #ifdef GM_VISBECK_VARIABLE_K
115 & +op5*(VisbeckK(i,j,bi,bj)+VisbeckK(i-1,j,bi,bj))
116 #endif
117 & )
118 #endif /* GM_NON_UNITY_DIAGONAL */
119 & *_recip_dxC(i,j,bi,bj)
120 & *(Tracer(i,j,k,bi,bj)-Tracer(i-1,j,k,bi,bj))
121 ENDDO
122 ENDDO
123
124 #ifdef GM_EXTRA_DIAGONAL
125 IF (GM_ExtraDiag) THEN
126 km1 = MAX(k-1,1)
127 kp1 = MIN(k+1,Nr)
128
129 DO j=jMin,jMax
130 DO i=iMin,iMax
131 C- Vertical gradients interpolated to U points
132 dTdz(i,j) = op5*(
133 & +op5*recip_drC(k)*
134 & ( maskC(i-1,j,k,bi,bj)*
135 & (Tracer(i-1,j,km1,bi,bj)-Tracer(i-1,j,k,bi,bj))
136 & +maskC( i ,j,k,bi,bj)*
137 & (Tracer( i ,j,km1,bi,bj)-Tracer( i ,j,k,bi,bj))
138 & )
139 & +op5*recip_drC(kp1)*
140 & ( maskC(i-1,j,kp1,bi,bj)*
141 & (Tracer(i-1,j,k,bi,bj)-Tracer(i-1,j,kp1,bi,bj))
142 & +maskC( i ,j,kp1,bi,bj)*
143 & (Tracer( i ,j,k,bi,bj)-Tracer( i ,j,kp1,bi,bj))
144 & ) )
145
146
147 ENDDO
148 ENDDO
149 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
150 CADJ STORE dtdz(:,:) =
151 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
152 #endif
153 DO j=jMin,jMax
154 DO i=iMin,iMax
155 C- Off-diagonal components of horizontal flux
156 df(i,j) = df(i,j) - xA(i,j)*Kuz(i,j,k,bi,bj)*dTdz(i,j)
157 ENDDO
158 ENDDO
159 ENDIF
160 #endif /* GM_EXTRA_DIAGONAL */
161
162 #ifdef GM_BOLUS_ADVEC
163 IF (GM_AdvForm .AND. GM_AdvSeparate
164 & .AND. .NOT.GM_InMomAsStress) THEN
165 kp1 = MIN(k+1,Nr)
166 maskp1 = 1.
167 IF (k.GE.Nr) maskp1 = 0.
168 DO j=jMin,jMax
169 DO i=iMin,iMax
170 uTrans(i,j) = dyG(i,j,bi,bj)*( GM_PsiX(i,j,kp1,bi,bj)*maskp1
171 & -GM_PsiX(i,j,k,bi,bj) )
172 & *maskW(i,j,k,bi,bj)
173 ENDDO
174 ENDDO
175 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
176 CADJ STORE utrans(:,:) =
177 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
178 #endif
179 DO j=jMin,jMax
180 DO i=iMin,iMax
181 df(i,j) = df(i,j)
182 & +uTrans(i,j)*op5*(Tracer(i,j,k,bi,bj)+Tracer(i-1,j,k,bi,bj))
183 ENDDO
184 ENDDO
185 ENDIF
186
187 #ifdef ALLOW_DIAGNOSTICS
188 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
189 IF ( useDiagnostics
190 & .AND. DIAGNOSTICS_IS_ON('GM_ubT ', myThid )
191 & .AND. tracerIdentity .EQ. 1) THEN
192 kp1 = MIN(k+1,Nr)
193 maskp1 = 1.
194 IF (k.GE.Nr) maskp1 = 0.
195 DO j=jMin,jMax
196 DO i=iMin,iMax
197 tmp1k(i,j) = dyG(i,j,bi,bj)*( GM_PsiX(i,j,kp1,bi,bj)*maskp1
198 & -GM_PsiX(i,j,k,bi,bj) )
199 & *maskW(i,j,k,bi,bj)
200 & *op5*(Tracer(i,j,k,bi,bj)+Tracer(i-1,j,k,bi,bj))
201 ENDDO
202 ENDDO
203 CALL DIAGNOSTICS_FILL(tmp1k,'GM_ubT ', k,1,2,bi,bj,myThid)
204
205 ENDIF
206 #endif /* ALLOW_DIAGNOSTICS */
207
208 #endif /* GM_BOLUS_ADVEC */
209
210 ENDIF
211 #endif /* ALLOW_GMREDI */
212
213 RETURN
214 END

  ViewVC Help
Powered by ViewVC 1.1.22