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

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

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


Revision 1.8 - (hide 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: +3 -2 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 heimbach 1.8 C $Header: /u/gcmpack/MITgcm/pkg/gmredi/gmredi_rtransport.F,v 1.5.2.2 2002/11/07 17:03:41 heimbach Exp $
2 adcroft 1.5 C $Name: $
3 adcroft 1.1
4     #include "GMREDI_OPTIONS.h"
5    
6     subroutine GMREDI_RTRANSPORT(
7     I iMin,iMax,jMin,jMax,bi,bj,K,
8 heimbach 1.8 I Tracer,tracerIdentity,
9 adcroft 1.1 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     C == Routine arguments ==
27     C iMin,iMax,jMin, - Range of points for which calculation
28     C jMax,bi,bj,k results will be set.
29     C xA - Area of X face
30     C Tracer - 3D Tracer field
31     C df - Diffusive flux component work array.
32     INTEGER iMin,iMax,jMin,jMax,bi,bj,k
33     _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
34     _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
35 heimbach 1.8 INTEGER tracerIdentity
36 adcroft 1.1 INTEGER myThid
37    
38     #ifdef ALLOW_GMREDI
39    
40     C == Local variables ==
41     C I, J - Loop counters
42     INTEGER I, J
43     _RL dTdx,dTdy
44 jmc 1.6 _RL rTrans
45 adcroft 1.1
46     C Surface flux is zero
47 heimbach 1.2 IF (useGMRedi .AND. K.GT.1) THEN
48 adcroft 1.1
49     DO j=jMin,jMax
50     DO i=iMin,iMax
51    
52     C- Horizontal gradients interpolated to W points
53     dTdx = 0.5*(
54     & +0.5*(_maskW(i+1,j,k,bi,bj)
55     & *_recip_dxC(i+1,j,bi,bj)*
56     & (Tracer(i+1,j,k,bi,bj)-Tracer(i,j,k,bi,bj))
57     & +_maskW(i,j,k,bi,bj)
58     & *_recip_dxC(i,j,bi,bj)*
59     & (Tracer(i,j,k,bi,bj)-Tracer(i-1,j,k,bi,bj)))
60     & +0.5*(_maskW(i+1,j,k-1,bi,bj)
61     & *_recip_dxC(i+1,j,bi,bj)*
62     & (Tracer(i+1,j,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj))
63     & +_maskW(i,j,k-1,bi,bj)
64     & *_recip_dxC(i,j,bi,bj)*
65     & (Tracer(i,j,k-1,bi,bj)-Tracer(i-1,j,k-1,bi,bj)))
66     & )
67    
68     dTdy = 0.5*(
69     & +0.5*(_maskS(i,j,k,bi,bj)
70     & *_recip_dyC(i,j,bi,bj)*
71     & (Tracer(i,j,k,bi,bj)-Tracer(i,j-1,k,bi,bj))
72     & +_maskS(i,j+1,k,bi,bj)
73     & *_recip_dyC(i,j+1,bi,bj)*
74     & (Tracer(i,j+1,k,bi,bj)-Tracer(i,j,k,bi,bj)))
75     & +0.5*(_maskS(i,j,k-1,bi,bj)
76     & *_recip_dyC(i,j,bi,bj)*
77     & (Tracer(i,j,k-1,bi,bj)-Tracer(i,j-1,k-1,bi,bj))
78     & +_maskS(i,j+1,k-1,bi,bj)
79     & *_recip_dyC(i,j+1,bi,bj)*
80     & (Tracer(i,j+1,k-1,bi,bj)-Tracer(i,j,k-1,bi,bj)))
81     & )
82    
83     C- Off-diagonal components of vertical flux
84     df(i,j) = df(i,j)
85     & - _rA(i,j,bi,bj)
86 jmc 1.6 & *( Kwx(i,j,k,bi,bj)*dTdx +Kwy(i,j,k,bi,bj)*dTdy )
87 adcroft 1.1
88     ENDDO
89     ENDDO
90 jmc 1.6
91     #ifdef GM_BOLUS_ADVEC
92 jmc 1.7 IF (GM_AdvForm .AND. GM_AdvSeparate) THEN
93 jmc 1.6 DO j=jMin,jMax
94     DO i=iMin,iMax
95     rTrans =
96     & dyG(i+1,j,bi,bj)*GM_PsiX(i+1,j,k,bi,bj)
97     & -dyG( i ,j,bi,bj)*GM_PsiX( i ,j,k,bi,bj)
98     & +dxG(i,j+1,bi,bj)*GM_PsiY(i,j+1,k,bi,bj)
99     & -dxG(i, j ,bi,bj)*GM_PsiY(i, j ,k,bi,bj)
100     df(i,j) = df(i,j)
101     & +rTrans*0.5
102     & *(Tracer(i,j,k,bi,bj)+Tracer(i,j,k-1,bi,bj))
103     ENDDO
104     ENDDO
105     ENDIF
106     #endif /* GM_BOLUS_ADVEC */
107 adcroft 1.1
108     c IF (.NOT.implicitDiffusion) THEN
109     c
110     c This vertical diffusion term is currently implemented
111     c by adding the VisbeckK*Kwz diffusivity to KappaRT/S
112     c See calc_diffusivity.F and calc_gt.F (calc_gs.F)
113     c
114     c DO j=jMin,jMax
115     c DO i=iMin,iMax
116     c df(i,j) = df(i,j) - _rA(i,j,bi,bj)
117 heimbach 1.3 c & *maskUp(i,j)*VisbeckK(i,j,bi,bj)*Kwz(i,j,k,bi,bj)
118 adcroft 1.1 c & *recip_drC(k)*rkfac
119     c & *(Tracer(i,j,k-1,bi,bj)-Tracer(i,j,k,bi,bj))
120     c ENDDO
121     c ENDDO
122     c ENDIF
123    
124     ENDIF
125     #endif /* ALLOW_GMREDI */
126    
127     RETURN
128     END

  ViewVC Help
Powered by ViewVC 1.1.22