/[MITgcm]/MITgcm/verification/global_with_CFC11/code1x1/calc_gtr1.F
ViewVC logotype

Annotation of /MITgcm/verification/global_with_CFC11/code1x1/calc_gtr1.F

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


Revision 1.1.2.1 - (hide annotations) (download)
Thu Aug 25 16:22:17 2005 UTC (18 years, 8 months ago) by dimitri
Branch: release1_50yr
Changes since 1.1: +114 -0 lines
adding ecco1x1 verification/global_with_CFC11 experiment

1 dimitri 1.1.2.1 C $Header: /u/gcmpack/MITgcm/verification/global_with_CFC11/code50yr/Attic/calc_gtr1.F,v 1.1.2.1 2003/05/04 23:19:18 dimitri Exp $
2     C $Name: release1_50yr $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: CALC_GTR1
8     C !INTERFACE:
9     SUBROUTINE CALC_GTR1(
10     I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
11     I xA,yA,uTrans,vTrans,rTrans,maskUp,
12     I KappaRT,
13     U fVerT,
14     I myTime,myIter,myThid )
15     C !DESCRIPTION: \bv
16     C *==========================================================*
17     C | SUBROUTINE CALC_GTR1
18     C | o Calculate the passive tracer tendency terms.
19     C *==========================================================*
20    
21     C !USES:
22     IMPLICIT NONE
23     C == GLobal variables ==
24     #include "SIZE.h"
25     #include "DYNVARS.h"
26     #include "EEPARAMS.h"
27     #include "PARAMS.h"
28     #include "GAD.h"
29     #ifdef ALLOW_PASSIVE_TRACER
30     #include "TR1.h"
31     #endif
32    
33     C !INPUT/OUTPUT PARAMETERS:
34     C == Routine arguments ==
35     C fVerT :: Flux of temperature (T) in the vertical
36     C direction at the upper(U) and lower(D) faces of a cell.
37     C maskUp :: Land mask used to denote base of the domain.
38     C xA :: Tracer cell face area normal to X
39     C yA :: Tracer cell face area normal to X
40     C uTrans :: Zonal volume transport through cell face
41     C vTrans :: Meridional volume transport through cell face
42     C rTrans :: Vertical volume transport through cell face
43     C bi, bj, iMin, iMax, jMin, jMax :: Range of points for which calculation
44     C results will be set.
45     C myThid - Instance number for this innvocation of CALC_GT
46     _RL fVerT (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
47     _RS xA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48     _RS yA (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
49     _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50     _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51     _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
52     _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
53     _RL KappaRT(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
54     INTEGER k,kUp,kDown,kM1
55     INTEGER bi,bj,iMin,iMax,jMin,jMax
56     _RL myTime
57     INTEGER myIter
58     INTEGER myThid
59    
60     CEOP
61    
62     #ifdef ALLOW_PASSIVE_TRACER
63     INTEGER i,j
64    
65     #ifdef ALLOW_AUTODIFF_TAMC
66     C-- only the kUp part of fverT is set in this subroutine
67     C-- the kDown is still required
68     fVerT(1,1,kDown) = fVerT(1,1,kDown)
69     #endif
70    
71     #ifdef INCLUDE_TR_FORCING_CODE
72     C-- External thermal forcing term(s)
73     CALL EXTERNAL_FORCING_TR(
74     I iMin,iMax,jMin,jMax,bi,bj,k,
75     I myTime,myThid)
76     #endif /* INCLUDE_TR_FORCING_CODE */
77    
78     CALL GAD_CALC_RHS(
79     I bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
80     I xA,yA,uTrans,vTrans,rTrans,maskUp,
81     I diffKhT, diffK4T, KappaRT, tr1,
82     I GAD_TR1, tracerAdvScheme,
83     U fVerT, gTr1,
84     I myThid )
85    
86     DO j=jMin,jMax
87     DO i=iMin,iMax
88     gTr1(i,j,1,bi,bj) = gTr1(i,j,1,bi,bj) +
89     & surfaceTendencyTr1(i,j,bi,bj)
90     ENDDO
91     ENDDO
92    
93     IF ( tracerAdvScheme.EQ.ENUM_CENTERED_2ND
94     & .OR.tracerAdvScheme.EQ.ENUM_UPWIND_3RD
95     & .OR.tracerAdvScheme.EQ.ENUM_CENTERED_4TH ) THEN
96     CALL ADAMS_BASHFORTH2(
97     I bi, bj, K,
98     U gTr1, gTr1nm1,
99     I myIter, myThid )
100     ENDIF
101    
102     #ifdef NONLIN_FRSURF
103     IF (nonlinFreeSurf.GT.0) THEN
104     CALL FREESURF_RESCALE_G(
105     I bi, bj, K,
106     U gTr1,
107     I myThid )
108     ENDIF
109     #endif /* NONLIN_FRSURF */
110    
111     #endif /* ALLOW_PASSIVE_TRACER */
112    
113     RETURN
114     END

  ViewVC Help
Powered by ViewVC 1.1.22