/[MITgcm]/MITgcm/pkg/ptracers/ptracers_calc_diff.F
ViewVC logotype

Annotation of /MITgcm/pkg/ptracers/ptracers_calc_diff.F

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


Revision 1.2 - (hide annotations) (download)
Fri Mar 25 00:28:43 2005 UTC (19 years, 2 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint58l_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint57f_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint57m_post, checkpoint58n_post, checkpoint58x_post, checkpoint57g_pre, checkpoint58t_post, checkpoint58h_post, checkpoint58w_post, checkpoint58j_post, checkpoint57h_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint58q_post, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint57h_done, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post
Changes since 1.1: +1 -2 lines
Fix argument list bug for CALL KPP_CALC_DIFF_S

1 heimbach 1.2 C $Header: /u/gcmpack/MITgcm/pkg/ptracers/ptracers_calc_diff.F,v 1.1 2004/10/22 16:02:00 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "PTRACERS_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: PTRACERS_CALC_DIFF
8     C !INTERFACE:
9     SUBROUTINE PTRACERS_CALC_DIFF(
10     I bi,bj,iMin,iMax,jMin,jMax,k,
11     I maskUp,
12     O KappaRtr,
13     I myThid)
14    
15     C !DESCRIPTION: \bv
16     C *==========================================================*
17     C | SUBROUTINE PTRACERS_CALC_DIFF
18     C | o Calculate net vertical diffusivity for passive tracers
19     C *==========================================================*
20     C | Combines spatially varying diffusion coefficients from
21     C | KPP and/or GM and/or convective stability test.
22     C *==========================================================*
23     C \ev
24    
25     C !USES:
26     IMPLICIT NONE
27     C == GLobal variables ==
28     #include "SIZE.h"
29     #include "EEPARAMS.h"
30     #include "PARAMS.h"
31     #include "GRID.h"
32     #include "DYNVARS.h"
33     #include "PTRACERS_SIZE.h"
34     #include "PTRACERS.h"
35     c #include "GAD.h"
36    
37     C !INPUT/OUTPUT PARAMETERS:
38     C == Routine arguments ==
39     C bi, bj :: tile indices
40     C iMin,iMax :: Range of points for which calculation is performed.
41     C jMin,jMax :: Range of points for which calculation is performed.
42     C maskUp :: land/water mask for Wvel points (above tracer level)
43     C myThid :: Instance number for this innvocation of PTRACERS_CALC_DIFF
44     C KappaRtr :: Net diffusivity for temperature
45     C KappaRS :: Net diffusivity for salinity
46     INTEGER bi,bj,iMin,iMax,jMin,jMax,k
47     _RS maskUp(1-Olx:sNx+Olx,1-Oly:sNy+Oly)
48     _RL KappaRtr(1-Olx:sNx+Olx,1-Oly:sNy+Oly,PTRACERS_num)
49     INTEGER myThid
50    
51     C !LOCAL VARIABLES:
52     C == Local variables ==
53     C I, J :: Loop counters
54     INTEGER i,j,iTr
55     _RL KbryanLewis79
56     CEOP
57    
58     KbryanLewis79=diffKrBL79surf+(diffKrBL79deep-diffKrBL79surf)
59     & *( atan( -( rF(k)-diffKrBL79Ho )/diffKrBL79scl )/PI+0.5 _d 0)
60    
61     C Loop over tracers
62     DO iTr=1,PTRACERS_numInUse
63    
64     DO j = 1-Oly, sNy+Oly
65     DO i = 1-Olx, sNx+Olx
66     KappaRtr(i,j,iTr) =
67     & IVDConvCount(i,j,k,bi,bj)*ivdc_kappa
68     #if (defined (ALLOW_AUTODIFF_TAMC) && defined (ALLOW_DIFFKR_CONTROL))
69     & + diffKr(i,j,k,bi,bj)
70     #else
71     & + PTRACERS_diffKrNr(k,iTr)
72     #endif
73     & + KbryanLewis79
74     ENDDO
75     ENDDO
76    
77     #ifdef ALLOW_GMREDI
78     IF ( PTRACERS_useGMRedi(iTr) ) THEN
79     CALL GMREDI_CALC_DIFF(
80     I bi,bj,iMin,iMax,jMin,jMax,k,1,
81     U KappaRtr(1-Olx,1-Oly,iTr),
82     I myThid)
83     ENDIF
84     #endif
85    
86     #ifdef ALLOW_KPP
87     IF ( PTRACERS_useKPP(iTr) ) THEN
88     CALL KPP_CALC_DIFF_S(
89     I bi,bj,iMin+1,iMax,jMin+1,jMax,k,1,
90     U KappaRtr(1-Olx,1-Oly,iTr),
91     I myThid)
92     ENDIF
93     #endif
94    
95     #ifdef ALLOW_PP81
96     IF (usePP81) THEN
97     CALL PP81_CALC_DIFF(
98     I bi,bj,iMin+1,iMax,jMin+1,jMax,k,1,
99     U KappaRtr(1-Olx,1-Oly,iTr),
100     I myThid)
101     ENDIF
102     #endif
103    
104     #ifdef ALLOW_MY82
105     IF (useMY82) THEN
106     CALL MY82_CALC_DIFF(
107     I bi,bj,iMin+1,iMax,jMin+1,jMax,k,1,
108     U KappaRtr(1-Olx,1-Oly,iTr),
109     I myThid)
110     ENDIF
111     #endif
112    
113     #ifdef ALLOW_GGL90
114     IF (useGGL90) THEN
115     CALL GGL90_CALC_DIFF(
116     I bi,bj,iMin+1,iMax,jMin+1,jMax,k,1,
117     U KappaRtr(1-Olx,1-Oly,iTr),
118     I myThid)
119     ENDIF
120     #endif
121    
122     C- Apply mask to vertical diffusivity
123     C jmc: don't have the impression that masking is needed
124     C but could be removed later if it's the case.
125     DO j = 1-Oly, sNy+Oly
126     DO i = 1-Olx, sNx+Olx
127     KappaRtr(i,j,iTr) = maskUp(i,j)*KappaRtr(i,j,iTr)
128     ENDDO
129     ENDDO
130    
131     C end of tracer loop
132     ENDDO
133    
134     RETURN
135     END

  ViewVC Help
Powered by ViewVC 1.1.22