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

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

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


Revision 1.4.4.2 - (hide annotations) (download)
Mon Apr 8 20:27:13 2002 UTC (22 years, 2 months ago) by heimbach
Branch: release1
CVS Tags: release1_p1, release1_p2, release1_p3, release1_p4, release1_p5, release1_p6
Changes since 1.4.4.1: +27 -2 lines
These changes constitute a patch to release1.
They were made on a development branch called "release1_final"
and are on the main trunk between chkpt44d_post and
checkpoint44h_post along with other changes.

This code is equivalent to chkpt44d_post with the following patches:
  - AD-related changes for GMRedi
  - fixes i KPP (delZ -> drF)
  - hook to OBCS songe layer code in external_forcing
  - errorMessageUnit non-zero in eeboot.F
  - modified test cost function and carbon verif.

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

  ViewVC Help
Powered by ViewVC 1.1.22