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

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

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


Revision 1.12 - (show annotations) (download)
Tue Jan 21 19:34:13 2003 UTC (21 years, 4 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint50c_post, checkpoint48e_post, checkpoint50c_pre, checkpoint48i_post, checkpoint51, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint48b_post, checkpoint48c_pre, checkpoint48d_pre, checkpoint48d_post, checkpoint48f_post, checkpoint48h_post, checkpoint51b_pre, checkpoint48a_post, checkpoint50f_post, checkpoint50a_post, checkpoint50f_pre, checkpoint47j_post, checkpoint48c_post, checkpoint50g_post, checkpoint50h_post, checkpoint50e_pre, checkpoint50i_post, checkpoint50e_post, checkpoint50d_pre, checkpoint48, checkpoint49, checkpoint48g_post, checkpoint50b_post, checkpoint51a_post
Changes since 1.11: +58 -12 lines
Yet more changes:
o adgmredi_calc_tensor
  avoiding all recomputation of gmredi_slope_limit
o adgmredi_x/y/rtransport
  added flag for excessive storing to avoid recomp. of
  u/v/rtans, dTdx/y/z
  -> this is not really necessary and very memory-consuming
o adgmredi_slope_psi:
  consistency with gmredi_slope_limit in treatment of GM_slopeSqCutoff
o gmredi_slope_limit
  re-activated full calculation of taperfct for case 'ac02'

1 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_rtransport.F,v 1.11 2003/01/10 00:48:39 heimbach Exp $
2 C $Name: $
3
4 #include "GMREDI_OPTIONS.h"
5
6 subroutine GMREDI_RTRANSPORT(
7 I iMin,iMax,jMin,jMax,bi,bj,K,
8 I Tracer,tracerIdentity,
9 U df,
10 I myThid)
11 C /==========================================================\
12 C | o SUBROUTINE GMREDI_RTRANSPORT |
13 C | Add vertical 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 _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
39 INTEGER tracerIdentity
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 _RL dTdx (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
49 _RL dTdy (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50 #ifdef GM_BOLUS_ADVEC
51 _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52 #endif
53
54 #ifdef ALLOW_AUTODIFF_TAMC
55 act0 = tracerIdentity - 1
56 max0 = maxpass
57 act1 = bi - myBxLo(myThid)
58 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
59 act2 = bj - myByLo(myThid)
60 max2 = myByHi(myThid) - myByLo(myThid) + 1
61 act3 = myThid - 1
62 max3 = nTx*nTy
63 act4 = ikey_dynamics - 1
64 igadkey = (act0 + 1)
65 & + act1*max0
66 & + act2*max0*max1
67 & + act3*max0*max1*max2
68 & + act4*max0*max1*max2*max3
69 kkey = (igadkey-1)*Nr + k
70 if (tracerIdentity.GT.maxpass)
71 & STOP 'maxpass seems smaller than tracerIdentity'
72 #endif /* ALLOW_AUTODIFF_TAMC */
73
74 C Surface flux is zero
75 IF (useGMRedi .AND. K.GT.1) THEN
76
77 C- Horizontal gradients interpolated to W points
78 DO j=jMin,jMax
79 DO i=iMin,iMax
80 dTdx(i,j) = op5*(
81 & +op5*(_maskW(i+1,j,k,bi,bj)
82 & *_recip_dxC(i+1,j,bi,bj)*
83 & (Tracer(i+1,j,k,bi,bj)-Tracer(i,j,k,bi,bj))
84 & +_maskW(i,j,k,bi,bj)
85 & *_recip_dxC(i,j,bi,bj)*
86 & (Tracer(i,j,k,bi,bj)-Tracer(i-1,j,k,bi,bj)))
87 & +op5*(_maskW(i+1,j,k-1,bi,bj)
88 & *_recip_dxC(i+1,j,bi,bj)*
89 & (Tracer(i+1,j,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj))
90 & +_maskW(i,j,k-1,bi,bj)
91 & *_recip_dxC(i,j,bi,bj)*
92 & (Tracer(i,j,k-1,bi,bj)-Tracer(i-1,j,k-1,bi,bj)))
93 & )
94
95 dTdy(i,j) = op5*(
96 & +op5*(_maskS(i,j,k,bi,bj)
97 & *_recip_dyC(i,j,bi,bj)*
98 & (Tracer(i,j,k,bi,bj)-Tracer(i,j-1,k,bi,bj))
99 & +_maskS(i,j+1,k,bi,bj)
100 & *_recip_dyC(i,j+1,bi,bj)*
101 & (Tracer(i,j+1,k,bi,bj)-Tracer(i,j,k,bi,bj)))
102 & +op5*(_maskS(i,j,k-1,bi,bj)
103 & *_recip_dyC(i,j,bi,bj)*
104 & (Tracer(i,j,k-1,bi,bj)-Tracer(i,j-1,k-1,bi,bj))
105 & +_maskS(i,j+1,k-1,bi,bj)
106 & *_recip_dyC(i,j+1,bi,bj)*
107 & (Tracer(i,j+1,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj)))
108 & )
109 ENDDO
110 ENDDO
111
112 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
113 CADJ STORE dTdx(:,:) =
114 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
115 CADJ STORE dTdy(:,:) =
116 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
117 #endif
118
119 C- Off-diagonal components of vertical flux
120 DO j=jMin,jMax
121 DO i=iMin,iMax
122 df(i,j) = df(i,j)
123 & - _rA(i,j,bi,bj)
124 & *( Kwx(i,j,k,bi,bj)*dTdx(i,j)+Kwy(i,j,k,bi,bj)*dTdy(i,j) )
125
126 ENDDO
127 ENDDO
128
129 #ifdef GM_BOLUS_ADVEC
130 IF (GM_AdvForm .AND. GM_AdvSeparate) THEN
131 DO j=jMin,jMax
132 DO i=iMin,iMax
133 rTrans(i,j) =
134 & dyG(i+1,j,bi,bj)*GM_PsiX(i+1,j,k,bi,bj)
135 & -dyG( i ,j,bi,bj)*GM_PsiX( i ,j,k,bi,bj)
136 & +dxG(i,j+1,bi,bj)*GM_PsiY(i,j+1,k,bi,bj)
137 & -dxG(i, j ,bi,bj)*GM_PsiY(i, j ,k,bi,bj)
138 ENDDO
139 ENDDO
140 #ifdef GM_AUTODIFF_EXCESSIVE_STORE
141 CADJ STORE rtrans(:,:) =
142 CADJ & comlev1_gmredi_k_gad, key=kkey, byte=isbyte
143 #endif
144 DO j=jMin,jMax
145 DO i=iMin,iMax
146 df(i,j) = df(i,j)
147 & +rTrans(i,j)*op5
148 & *(Tracer(i,j,k,bi,bj)+Tracer(i,j,k-1,bi,bj))
149 ENDDO
150 ENDDO
151 ENDIF
152 #endif /* GM_BOLUS_ADVEC */
153
154 c IF (.NOT.implicitDiffusion) THEN
155 c
156 c This vertical diffusion term is currently implemented
157 c by adding the VisbeckK*Kwz diffusivity to KappaRT/S
158 c See calc_diffusivity.F and calc_gt.F (calc_gs.F)
159 c
160 c DO j=jMin,jMax
161 c DO i=iMin,iMax
162 c df(i,j) = df(i,j) - _rA(i,j,bi,bj)
163 c & *maskUp(i,j)*VisbeckK(i,j,bi,bj)*Kwz(i,j,k,bi,bj)
164 c & *recip_drC(k)*rkfac
165 c & *(Tracer(i,j,k-1,bi,bj)-Tracer(i,j,k,bi,bj))
166 c ENDDO
167 c ENDDO
168 c ENDIF
169
170 ENDIF
171 #endif /* ALLOW_GMREDI */
172
173 RETURN
174 END

  ViewVC Help
Powered by ViewVC 1.1.22