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

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

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


Revision 1.8 - (show annotations) (download)
Tue Nov 12 20:42:24 2002 UTC (21 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint46n_post
Changes since 1.7: +22 -8 lines
Merging from release1_p8 branch:
o GAD:
  - generated new common blocks to account for call of
    same gad routines with differing traceridentities
    (needed to modify tracerIdentity indices in GAD.h)
  - generated separate common blocks for case useCubedSphereExchange
    (Department of Futurology)
  - parameter lists to gmredi_?transport: added tracerIdentity
  - added new key indices to tamc.h

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_ytransport.F,v 1.4.4.3 2002/11/07 17:03:41 heimbach Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 subroutine GMREDI_YTRANSPORT(
7 I iMin,iMax,jMin,jMax,bi,bj,K,
8 I yA,Tracer,tracerIdentity,
9 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
26 #ifdef ALLOW_AUTODIFF_TAMC
27 #include "tamc.h"
28 #include "tamc_keys.h"
29 #endif /* ALLOW_AUTODIFF_TAMC */
30
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 _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41 INTEGER tracerIdentity
42 INTEGER myThid
43
44 #ifdef ALLOW_GMREDI
45
46 C == Local variables ==
47 C I, J - Loop counters
48 INTEGER I, J
49 INTEGER km1,kp1
50 _RL vTrans, maskp1, dTdz
51
52 #ifdef ALLOW_AUTODIFF_TAMC
53 act0 = tracerIdentity - 1
54 max0 = maxpass
55 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 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 #endif /* ALLOW_AUTODIFF_TAMC */
71
72 IF (useGMRedi) THEN
73
74 #ifdef ALLOW_AUTODIFF_TAMC
75 # 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 #endif
84
85 C-- Area integrated meridional flux
86 DO j=jMin,jMax
87 DO i=iMin,iMax
88 df(i,j) = df(i,j)
89 & -yA(i,j)
90 #ifdef GM_NON_UNITY_DIAGONAL
91 & *Kvy(i,j,k,bi,bj)
92 #else
93 & *(GM_isopycK
94 #ifdef GM_VISBECK_VARIABLE_K
95 & +0.5*(VisbeckK(i,j,bi,bj)+VisbeckK(i,j-1,bi,bj))
96 #endif
97 & )
98 #endif /* GM_NON_UNITY_DIAGONAL */
99 & *_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
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 dTdz = 0.5*(
114 & +0.5*recip_drC(k)*
115 & ( 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 & +0.5*recip_drC(kp1)*
121 & ( 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 IF (GM_AdvForm .AND. GM_AdvSeparate) THEN
137 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 & +vTrans*0.5*(Tracer(i,j,k,bi,bj)+Tracer(i,j-1,k,bi,bj))
147 ENDDO
148 ENDDO
149 ENDIF
150 #endif /* GM_BOLUS_ADVEC */
151
152 ENDIF
153 #endif /* ALLOW_GMREDI */
154
155 RETURN
156 END

  ViewVC Help
Powered by ViewVC 1.1.22