/[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.5 - (hide annotations) (download)
Sun Dec 16 18:54:49 2001 UTC (22 years, 6 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_post, checkpoint43a-release1mods, chkpt44d_post, checkpoint44e_pre, release1-branch_tutorials, chkpt44a_post, chkpt44c_pre, checkpoint44g_post, release1-branch-end, checkpoint44b_post, chkpt44a_pre, checkpoint44b_pre, checkpoint44, chkpt44c_post, checkpoint44f_pre, release1-branch_branchpoint
Branch point for: release1_final, release1-branch
Changes since 1.4: +59 -8 lines
Modification to the GMREDI package :
 change units of tensor-K arrays, scale now like diffusivity
 initialise all common block arrays in S/R gmredi_init
 add option to use different isopycnal(Redi) & GM diffusivity
 add option to use the advective GM form or the skew-flux form (=default)
 bug in non_unity_diagonal part fixed.

1 jmc 1.5 C $Header: /u/gcmpack/models/MITgcmUV/pkg/gmredi/gmredi_ytransport.F,v 1.4 2001/02/04 14:38:49 cnh Exp $
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     I yA,Tracer,
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     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     _RS yA(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
34     _RL Tracer(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
35     _RL df (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
36     INTEGER myThid
37    
38     #ifdef ALLOW_GMREDI
39    
40     C == Local variables ==
41     C I, J - Loop counters
42     INTEGER I, J
43 jmc 1.5 INTEGER km1,kp1
44     _RL vTrans, maskp1, dTdz
45 adcroft 1.1
46 heimbach 1.2 IF (useGMRedi) THEN
47 adcroft 1.1
48     C-- Area integrated meridional flux
49     DO j=jMin,jMax
50     DO i=iMin,iMax
51     df(i,j) = df(i,j)
52 jmc 1.5 & -yA(i,j)
53 adcroft 1.1 #ifdef GM_NON_UNITY_DIAGONAL
54 heimbach 1.3 & *Kvy(i,j,k,bi,bj)
55 jmc 1.5 #else
56     & *(GM_isopycK
57     #ifdef GM_VISBECK_VARIABLE_K
58     & +0.5*(VisbeckK(i,j,bi,bj)+VisbeckK(i,j-1,bi,bj))
59 adcroft 1.1 #endif
60 jmc 1.5 & )
61     #endif /* GM_NON_UNITY_DIAGONAL */
62 adcroft 1.1 & *_recip_dyC(i,j,bi,bj)
63     & *(Tracer(i,j,k,bi,bj)-Tracer(i,j-1,k,bi,bj))
64     ENDDO
65     ENDDO
66 jmc 1.5
67     #ifdef GM_EXTRA_DIAGONAL
68     IF (GM_ExtraDiag) THEN
69     km1 = MAX(k-1,1)
70     kp1 = MIN(k+1,Nr)
71    
72     DO j=jMin,jMax
73     DO i=iMin,iMax
74    
75     C- Vertical gradients interpolated to V points
76     dTdz = 0.5*(
77     & +0.5*recip_drC(k)*
78     & ( maskC(i,j-1,k,bi,bj)*
79     & (Tracer(i,j-1,km1,bi,bj)-Tracer(i,j-1,k,bi,bj))
80     & +maskC(i, j ,k,bi,bj)*
81     & (Tracer(i, j ,km1,bi,bj)-Tracer(i, j ,k,bi,bj))
82     & )
83     & +0.5*recip_drC(kp1)*
84     & ( maskC(i,j-1,kp1,bi,bj)*
85     & (Tracer(i,j-1,k,bi,bj)-Tracer(i,j-1,kp1,bi,bj))
86     & +maskC(i, j ,kp1,bi,bj)*
87     & (Tracer(i, j ,k,bi,bj)-Tracer(i, j ,kp1,bi,bj))
88     & ) )
89    
90     C- Off-diagonal components of horizontal flux
91     df(i,j) = df(i,j) - yA(i,j)*Kvz(i,j,k,bi,bj)*dTdz
92    
93     ENDDO
94     ENDDO
95     ENDIF
96     #endif /* GM_EXTRA_DIAGONAL */
97    
98     #ifdef GM_BOLUS_ADVEC
99     IF (GM_AdvForm) THEN
100     kp1 = MIN(k+1,Nr)
101     maskp1 = 1.
102     IF (k.GE.Nr) maskp1 = 0.
103     DO j=jMin,jMax
104     DO i=iMin,iMax
105     vTrans = dxG(i,j,bi,bj)*( GM_PsiY(i,j,kp1,bi,bj)*maskp1
106     & -GM_PsiY(i,j,k,bi,bj) )
107     & *maskS(i,j,k,bi,bj)
108     df(i,j) = df(i,j)
109     & +vTrans*0.5*(Tracer(i,j,k,bi,bj)+Tracer(i,j-1,k,bi,bj))
110     ENDDO
111     ENDDO
112     ENDIF
113     #endif /* GM_BOLUS_ADVEC */
114 adcroft 1.1
115     ENDIF
116     #endif /* ALLOW_GMREDI */
117    
118     RETURN
119     END

  ViewVC Help
Powered by ViewVC 1.1.22