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

Diff of /MITgcm/model/src/calc_gs.F

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

revision 1.33 by jmc, Sat Jun 15 03:28:39 2002 UTC revision 1.42 by heimbach, Thu Dec 8 15:44:33 2005 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2  C $Name$  C $Name$
3    
4    #include "PACKAGES_CONFIG.h"
5  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
6    
7  CBOP  CBOP
# Line 8  C     !ROUTINE: CALC_GS Line 9  C     !ROUTINE: CALC_GS
9  C     !INTERFACE:  C     !INTERFACE:
10        SUBROUTINE CALC_GS(        SUBROUTINE CALC_GS(
11       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
12       I           xA,yA,uTrans,vTrans,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
13       I           KappaRS,       I           KappaRS,
14       U           fVerS,       U           fVerS,
15       I           myTime,myIter,myThid )       I           myTime,myIter,myThid )
# Line 47  C     == GLobal variables == Line 48  C     == GLobal variables ==
48  #include "DYNVARS.h"  #include "DYNVARS.h"
49  #include "EEPARAMS.h"  #include "EEPARAMS.h"
50  #include "PARAMS.h"  #include "PARAMS.h"
51    #ifdef ALLOW_GENERIC_ADVDIFF
52  #include "GAD.h"  #include "GAD.h"
53    #endif
54    #ifdef ALLOW_AUTODIFF_TAMC
55    # include "tamc.h"
56    # include "tamc_keys.h"
57    #endif
58    
59  C     !INPUT/OUTPUT PARAMETERS:  C     !INPUT/OUTPUT PARAMETERS:
60  C     == Routine arguments ==  C     == Routine arguments ==
# Line 58  C     xA      :: Tracer cell face area n Line 65  C     xA      :: Tracer cell face area n
65  C     yA      :: Tracer cell face area normal to X  C     yA      :: Tracer cell face area normal to X
66  C     uTrans  :: Zonal volume transport through cell face  C     uTrans  :: Zonal volume transport through cell face
67  C     vTrans  :: Meridional volume transport through cell face  C     vTrans  :: Meridional volume transport through cell face
68  C     rTrans  :: Vertical volume transport through cell face  C     rTrans  ::   Vertical volume transport at interface k
69    C     rTransKp1 :: Vertical volume transport at inteface k+1
70  C     bi, bj, iMin, iMax, jMin, jMax :: Range of points for which calculation  C     bi, bj, iMin, iMax, jMin, jMax :: Range of points for which calculation
71  C                                      results will be set.  C                                      results will be set.
72  C     myThid :: Instance number for this innvocation of CALC_GT  C     myThid :: Instance number for this innvocation of CALC_GT
# Line 68  C     myThid :: Instance number for this Line 76  C     myThid :: Instance number for this
76        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
77        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
78        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
79          _RL rTransKp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
80        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
81        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
82        INTEGER k,kUp,kDown,kM1        INTEGER k,kUp,kDown,kM1
83        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
84        _RL     myTime        _RL     myTime
# Line 78  C     myThid :: Instance number for this Line 87  C     myThid :: Instance number for this
87    
88  CEOP  CEOP
89    
90    #ifdef ALLOW_GENERIC_ADVDIFF
91  C     === Local variables ===  C     === Local variables ===
92        LOGICAL calcAdvection        LOGICAL calcAdvection
93          INTEGER iterNb
94    #ifdef ALLOW_ADAMSBASHFORTH_3
95          INTEGER m1, m2
96    #endif
97    
98    #ifdef ALLOW_AUTODIFF_TAMC
99              act1 = bi - myBxLo(myThid)
100              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
101              act2 = bj - myByLo(myThid)
102              max2 = myByHi(myThid) - myByLo(myThid) + 1
103              act3 = myThid - 1
104              max3 = nTx*nTy
105              act4 = ikey_dynamics - 1
106              itdkey = (act1 + 1) + act2*max1
107         &                      + act3*max1*max2
108         &                      + act4*max1*max2*max3
109              kkey = (itdkey-1)*Nr + k
110    #endif /* ALLOW_AUTODIFF_TAMC */
111    
112  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
113  C--   only the kUp part of fverS is set in this subroutine  C--   only the kUp part of fverS is set in this subroutine
114  C--   the kDown is still required  C--   the kDown is still required
115        fVerS(1,1,kDown) = fVerS(1,1,kDown)        fVerS(1,1,kDown) = fVerS(1,1,kDown)
116    # ifdef NONLIN_FRSURF
117    CADJ STORE fVerS(:,:,:) = comlev1_bibj_k, key=kkey, byte=isbyte
118    # endif
119  #endif  #endif
120    
121    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
122    
123        calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec        calcAdvection = saltAdvection .AND. .NOT.saltMultiDimAdvec
124        CALL GAD_CALC_RHS(        iterNb = myIter
125          IF (staggerTimeStep) iterNb = myIter - 1
126    
127    #ifdef ALLOW_ADAMSBASHFORTH_3
128          IF ( AdamsBashforth_S ) THEN
129            m1 = 1 + MOD(iterNb+1,2)
130            m2 = 1 + MOD( iterNb ,2)
131            CALL GAD_CALC_RHS(
132       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
133       I           xA,yA,uTrans,vTrans,rTrans,maskUp,       I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
134       I           diffKhS, diffK4S, KappaRS, Salt,       I           uVel, vVel, wVel,
135       I           GAD_SALINITY, saltAdvScheme, calcAdvection,       I           diffKhS, diffK4S, KappaRS,
136         I           gsNm(1-Olx,1-Oly,1,1,1,m2), salt,
137         I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
138         I           calcAdvection, saltImplVertAdv,
139       U           fVerS, gS,       U           fVerS, gS,
140       I           myThid )       I           myTime, myIter, myThid )
141          ELSE
142    #endif /* ALLOW_ADAMSBASHFORTH_3 */
143            CALL GAD_CALC_RHS(
144         I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
145         I           xA,yA,uTrans,vTrans,rTrans,rTransKp1,maskUp,
146         I           uVel, vVel, wVel,
147         I           diffKhS, diffK4S, KappaRS, salt, salt,
148         I           GAD_SALINITY, saltAdvScheme, saltVertAdvScheme,
149         I           calcAdvection, saltImplVertAdv,
150         U           fVerS, gS,
151         I           myTime, myIter, myThid )
152    #ifdef ALLOW_ADAMSBASHFORTH_3
153          ENDIF
154    #endif
155    
156  C--   External salinity forcing term(s) inside Adams-Bashforth:  C--   External salinity forcing term(s) inside Adams-Bashforth:
157        IF ( saltForcing .AND. forcing_In_AB )        IF ( saltForcing .AND. forcing_In_AB )
# Line 102  C--   External salinity forcing term(s) Line 159  C--   External salinity forcing term(s)
159       I     iMin,iMax,jMin,jMax,bi,bj,k,       I     iMin,iMax,jMin,jMax,bi,bj,k,
160       I     myTime,myThid)       I     myTime,myThid)
161    
162        IF ( saltAdamsBashforth ) THEN        IF ( AdamsBashforthGs ) THEN
163    #ifdef ALLOW_ADAMSBASHFORTH_3
164            CALL ADAMS_BASHFORTH3(
165         I                        bi, bj, k,
166         U                        gS, gsNm,
167         I                        saltStartAB, iterNb, myThid )
168    #else
169          CALL ADAMS_BASHFORTH2(          CALL ADAMS_BASHFORTH2(
170       I                        bi, bj, K,       I                        bi, bj, k,
171       U                        gS, gSnm1,       U                        gS, gsNm1,
172       I                        myIter, myThid )       I                        iterNb, myThid )
173    #endif
174        ENDIF        ENDIF
175    
176  C--   External salinity forcing term(s) outside Adams-Bashforth:  C--   External salinity forcing term(s) outside Adams-Bashforth:
# Line 118  C--   External salinity forcing term(s) Line 182  C--   External salinity forcing term(s)
182  #ifdef NONLIN_FRSURF  #ifdef NONLIN_FRSURF
183        IF (nonlinFreeSurf.GT.0) THEN        IF (nonlinFreeSurf.GT.0) THEN
184          CALL FREESURF_RESCALE_G(          CALL FREESURF_RESCALE_G(
185       I                          bi, bj, K,       I                          bi, bj, k,
186       U                          gS,       U                          gS,
187       I                          myThid )       I                          myThid )
188            IF ( AdamsBashforthGs ) THEN
189    #ifdef ALLOW_ADAMSBASHFORTH_3
190            CALL FREESURF_RESCALE_G(
191         I                          bi, bj, k,
192         U                          gsNm(1-OLx,1-OLy,1,1,1,1),
193         I                          myThid )
194            CALL FREESURF_RESCALE_G(
195         I                          bi, bj, k,
196         U                          gsNm(1-OLx,1-OLy,1,1,1,2),
197         I                          myThid )
198    #else
199            CALL FREESURF_RESCALE_G(
200         I                          bi, bj, k,
201         U                          gsNm1,
202         I                          myThid )
203    #endif
204            ENDIF
205        ENDIF        ENDIF
206  #endif /* NONLIN_FRSURF */  #endif /* NONLIN_FRSURF */
207    
208    #endif /* ALLOW_GENERIC_ADVDIFF */
209    
210        RETURN        RETURN
211        END        END

Legend:
Removed from v.1.33  
changed lines
  Added in v.1.42

  ViewVC Help
Powered by ViewVC 1.1.22