/[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.7 - (show annotations) (download)
Sun Mar 24 02:33:16 2002 UTC (22 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46l_post, checkpoint46g_pre, checkpoint46f_post, checkpoint46b_post, checkpoint46l_pre, checkpoint46d_pre, checkpoint45d_post, checkpoint46j_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: +25 -2 lines
Various modifications to generate more stable adjoint of GMRedi.

1
2 #include "GMREDI_OPTIONS.h"
3
4 subroutine GMREDI_XTRANSPORT(
5 I iMin,iMax,jMin,jMax,bi,bj,K,
6 I xA,Tracer,
7 U df,
8 I myThid)
9 C /==========================================================\
10 C | o SUBROUTINE GMREDI_XTRANSPORT |
11 C | Add horizontal x transport terms from GM/Redi |
12 C | parameterization. |
13 C |==========================================================|
14 C \==========================================================/
15 IMPLICIT NONE
16
17 C == GLobal variables ==
18 #include "SIZE.h"
19 #include "EEPARAMS.h"
20 #include "PARAMS.h"
21 #include "GRID.h"
22 #include "GMREDI.h"
23
24 #ifdef ALLOW_AUTODIFF_TAMC
25 #include "tamc.h"
26 #include "tamc_keys.h"
27 #endif /* ALLOW_AUTODIFF_TAMC */
28
29 C == Routine arguments ==
30 C iMin,iMax,jMin, - Range of points for which calculation
31 C jMax,bi,bj,k results will be set.
32 C xA - Area of X face
33 C Tracer - 3D Tracer field
34 C df - Diffusive flux component work array.
35 INTEGER iMin,iMax,jMin,jMax,bi,bj,k
36 _RS xA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
37 _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
38 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39 INTEGER myThid
40
41 #ifdef ALLOW_GMREDI
42
43 C == Local variables ==
44 C I, J - Loop counters
45 INTEGER I, J
46 INTEGER km1,kp1
47 _RL uTrans, maskp1, dTdz
48
49 #ifdef ALLOW_AUTODIFF_TAMC
50 act1 = bi - myBxLo(myThid)
51 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
52 act2 = bj - myByLo(myThid)
53 max2 = myByHi(myThid) - myByLo(myThid) + 1
54 act3 = myThid - 1
55 max3 = nTx*nTy
56 act4 = ikey_dynamics - 1
57 ikey = (act1 + 1) + act2*max1
58 & + act3*max1*max2
59 & + act4*max1*max2*max3
60 kkey = (ikey-1)*Nr + k
61 #endif /* ALLOW_AUTODIFF_TAMC */
62
63 IF (useGMRedi) THEN
64
65 #ifdef GM_NON_UNITY_DIAGONAL
66 #ifdef ALLOW_AUTODIFF_TAMC
67 CADJ STORE Kux(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
68 #endif
69 #endif
70
71 C-- Area integrated zonal flux
72 DO j=jMin,jMax
73 DO i=iMin,iMax
74 df(i,j) = df(i,j)
75 & -xA(i,j)
76 #ifdef GM_NON_UNITY_DIAGONAL
77 & *Kux(i,j,k,bi,bj)
78 #else
79 & *(GM_isopycK
80 #ifdef GM_VISBECK_VARIABLE_K
81 & +0.5*(VisbeckK(i,j,bi,bj)+VisbeckK(i-1,j,bi,bj))
82 #endif
83 & )
84 #endif /* GM_NON_UNITY_DIAGONAL */
85 & *_recip_dxC(i,j,bi,bj)
86 & *(Tracer(i,j,k,bi,bj)-Tracer(i-1,j,k,bi,bj))
87 ENDDO
88 ENDDO
89
90 #ifdef GM_EXTRA_DIAGONAL
91 IF (GM_ExtraDiag) THEN
92 km1 = MAX(k-1,1)
93 kp1 = MIN(k+1,Nr)
94
95 DO j=jMin,jMax
96 DO i=iMin,iMax
97
98 C- Vertical gradients interpolated to U points
99 dTdz = 0.5*(
100 & +0.5*recip_drC(k)*
101 & ( maskC(i-1,j,k,bi,bj)*
102 & (Tracer(i-1,j,km1,bi,bj)-Tracer(i-1,j,k,bi,bj))
103 & +maskC( i ,j,k,bi,bj)*
104 & (Tracer( i ,j,km1,bi,bj)-Tracer( i ,j,k,bi,bj))
105 & )
106 & +0.5*recip_drC(kp1)*
107 & ( maskC(i-1,j,kp1,bi,bj)*
108 & (Tracer(i-1,j,k,bi,bj)-Tracer(i-1,j,kp1,bi,bj))
109 & +maskC( i ,j,kp1,bi,bj)*
110 & (Tracer( i ,j,k,bi,bj)-Tracer( i ,j,kp1,bi,bj))
111 & ) )
112
113 C- Off-diagonal components of horizontal flux
114 df(i,j) = df(i,j) - xA(i,j)*Kuz(i,j,k,bi,bj)*dTdz
115
116 ENDDO
117 ENDDO
118 ENDIF
119 #endif /* GM_EXTRA_DIAGONAL */
120
121 #ifdef GM_BOLUS_ADVEC
122 IF (GM_AdvForm .AND. GM_AdvSeparate) THEN
123 kp1 = MIN(k+1,Nr)
124 maskp1 = 1.
125 IF (k.GE.Nr) maskp1 = 0.
126 DO j=jMin,jMax
127 DO i=iMin,iMax
128 uTrans = dyG(i,j,bi,bj)*( GM_PsiX(i,j,kp1,bi,bj)*maskp1
129 & -GM_PsiX(i,j,k,bi,bj) )
130 & *maskW(i,j,k,bi,bj)
131 df(i,j) = df(i,j)
132 & +uTrans*0.5*(Tracer(i,j,k,bi,bj)+Tracer(i-1,j,k,bi,bj))
133 ENDDO
134 ENDDO
135 ENDIF
136 #endif /* GM_BOLUS_ADVEC */
137
138 ENDIF
139 #endif /* ALLOW_GMREDI */
140
141 RETURN
142 END

  ViewVC Help
Powered by ViewVC 1.1.22