/[MITgcm]/MITgcm/model/src/calc_gtr1.F
ViewVC logotype

Annotation of /MITgcm/model/src/calc_gtr1.F

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


Revision 1.5 - (hide annotations) (download)
Thu Sep 20 18:00:15 2001 UTC (22 years, 8 months ago) by adcroft
Branch: MAIN
CVS Tags: checkpoint40
Changes since 1.4: +2 -2 lines
Changed arguments to adams_bashforth2() to refer to gTr1 and not gT.

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

  ViewVC Help
Powered by ViewVC 1.1.22