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

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

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


Revision 1.11 - (hide annotations) (download)
Sun Jan 12 21:13:36 2003 UTC (21 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint47i_post
Changes since 1.10: +3 -1 lines
was easy to fix (sorry Patrick ...)

1 jmc 1.11 C $Header: $
2     C $Name: $
3 adcroft 1.1
4     #include "GMREDI_OPTIONS.h"
5    
6     subroutine GMREDI_YTRANSPORT(
7     I iMin,iMax,jMin,jMax,bi,bj,K,
8 heimbach 1.8 I yA,Tracer,tracerIdentity,
9 adcroft 1.1 U df,
10     I myThid)
11     C /==========================================================\
12     C | o SUBROUTINE GMREDI_YTRANSPORT |
13     C | Add horizontal y 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 heimbach 1.7
26     #ifdef ALLOW_AUTODIFF_TAMC
27     #include "tamc.h"
28     #include "tamc_keys.h"
29     #endif /* ALLOW_AUTODIFF_TAMC */
30 adcroft 1.1
31     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 yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
39     _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
40 heimbach 1.9 integer tracerIdentity
41 adcroft 1.1 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
42     INTEGER myThid
43    
44     #ifdef ALLOW_GMREDI
45    
46     C == Local variables ==
47     C I, J - Loop counters
48     INTEGER I, J
49 jmc 1.5 INTEGER km1,kp1
50     _RL vTrans, maskp1, dTdz
51 adcroft 1.1
52 heimbach 1.7 #ifdef ALLOW_AUTODIFF_TAMC
53 heimbach 1.8 act0 = tracerIdentity - 1
54     max0 = maxpass
55 heimbach 1.7 act1 = bi - myBxLo(myThid)
56     max1 = myBxHi(myThid) - myBxLo(myThid) + 1
57     act2 = bj - myByLo(myThid)
58     max2 = myByHi(myThid) - myByLo(myThid) + 1
59     act3 = myThid - 1
60     max3 = nTx*nTy
61     act4 = ikey_dynamics - 1
62 heimbach 1.8 igadkey = (act0 + 1)
63     & + act1*max0
64     & + act2*max0*max1
65     & + act3*max0*max1*max2
66     & + act4*max0*max1*max2*max3
67     kkey = (igadkey-1)*Nr + k
68     if (tracerIdentity.GT.maxpass)
69     & STOP 'maxpass seems smaller than tracerIdentity'
70 heimbach 1.7 #endif /* ALLOW_AUTODIFF_TAMC */
71    
72 heimbach 1.2 IF (useGMRedi) THEN
73 heimbach 1.7
74     #ifdef ALLOW_AUTODIFF_TAMC
75 heimbach 1.8 # ifdef GM_NON_UNITY_DIAGONAL
76     CADJ STORE Kvy(:,:,k,bi,bj) =
77     CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
78     # endif
79     # ifdef GM_EXTRA_DIAGONAL
80     CADJ STORE Kvz(:,:,k,bi,bj) =
81     CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
82     # endif
83 heimbach 1.7 #endif
84 adcroft 1.1
85     C-- Area integrated meridional flux
86     DO j=jMin,jMax
87     DO i=iMin,iMax
88     df(i,j) = df(i,j)
89 jmc 1.5 & -yA(i,j)
90 adcroft 1.1 #ifdef GM_NON_UNITY_DIAGONAL
91 heimbach 1.3 & *Kvy(i,j,k,bi,bj)
92 jmc 1.5 #else
93     & *(GM_isopycK
94     #ifdef GM_VISBECK_VARIABLE_K
95 jmc 1.11 & +op5*(VisbeckK(i,j,bi,bj)+VisbeckK(i,j-1,bi,bj))
96 adcroft 1.1 #endif
97 jmc 1.5 & )
98     #endif /* GM_NON_UNITY_DIAGONAL */
99 adcroft 1.1 & *_recip_dyC(i,j,bi,bj)
100     & *(Tracer(i,j,k,bi,bj)-Tracer(i,j-1,k,bi,bj))
101     ENDDO
102     ENDDO
103 jmc 1.5
104     #ifdef GM_EXTRA_DIAGONAL
105     IF (GM_ExtraDiag) THEN
106     km1 = MAX(k-1,1)
107     kp1 = MIN(k+1,Nr)
108    
109     DO j=jMin,jMax
110     DO i=iMin,iMax
111    
112     C- Vertical gradients interpolated to V points
113 heimbach 1.10 dTdz = op5*(
114     & +op5*recip_drC(k)*
115 jmc 1.5 & ( maskC(i,j-1,k,bi,bj)*
116     & (Tracer(i,j-1,km1,bi,bj)-Tracer(i,j-1,k,bi,bj))
117     & +maskC(i, j ,k,bi,bj)*
118     & (Tracer(i, j ,km1,bi,bj)-Tracer(i, j ,k,bi,bj))
119     & )
120 heimbach 1.10 & +op5*recip_drC(kp1)*
121 jmc 1.5 & ( maskC(i,j-1,kp1,bi,bj)*
122     & (Tracer(i,j-1,k,bi,bj)-Tracer(i,j-1,kp1,bi,bj))
123     & +maskC(i, j ,kp1,bi,bj)*
124     & (Tracer(i, j ,k,bi,bj)-Tracer(i, j ,kp1,bi,bj))
125     & ) )
126    
127     C- Off-diagonal components of horizontal flux
128     df(i,j) = df(i,j) - yA(i,j)*Kvz(i,j,k,bi,bj)*dTdz
129    
130     ENDDO
131     ENDDO
132     ENDIF
133     #endif /* GM_EXTRA_DIAGONAL */
134    
135     #ifdef GM_BOLUS_ADVEC
136 jmc 1.6 IF (GM_AdvForm .AND. GM_AdvSeparate) THEN
137 jmc 1.5 kp1 = MIN(k+1,Nr)
138     maskp1 = 1.
139     IF (k.GE.Nr) maskp1 = 0.
140     DO j=jMin,jMax
141     DO i=iMin,iMax
142     vTrans = dxG(i,j,bi,bj)*( GM_PsiY(i,j,kp1,bi,bj)*maskp1
143     & -GM_PsiY(i,j,k,bi,bj) )
144     & *maskS(i,j,k,bi,bj)
145     df(i,j) = df(i,j)
146 heimbach 1.10 & +vTrans*op5*(Tracer(i,j,k,bi,bj)+Tracer(i,j-1,k,bi,bj))
147 jmc 1.5 ENDDO
148     ENDDO
149     ENDIF
150     #endif /* GM_BOLUS_ADVEC */
151 adcroft 1.1
152     ENDIF
153     #endif /* ALLOW_GMREDI */
154    
155     RETURN
156     END

  ViewVC Help
Powered by ViewVC 1.1.22