/[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.1 by cnh, Wed Apr 22 19:15:30 1998 UTC revision 1.31 by adcroft, Wed Sep 19 02:43:27 2001 UTC
# Line 1  Line 1 
1  C $Id$  C $Header$
2    C $Name$
3    
4  #include "CPP_EEOPTIONS.h"  #include "CPP_OPTIONS.h"
5    
 CStartOfInterFace  
6        SUBROUTINE CALC_GS(        SUBROUTINE CALC_GS(
7       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,       I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
8       I           xA,yA,uTrans,vTrans,wTrans,maskup,       I           xA,yA,uTrans,vTrans,rTrans,maskUp,
9       U           af,df,fZon,fMer, fVerS,       I           KappaRS,
10       I           myThid )       U           fVerS,
11         I           myTime,myIter,myThid )
12  C     /==========================================================\  C     /==========================================================\
13  C     | SUBROUTINE CALC_GS                                       |  C     | SUBROUTINE CALC_GS                                       |
14  C     | o Calculate the salinity tendency terms.                 |  C     | o Calculate the salt tendency terms.                     |
15  C     |==========================================================|  C     |==========================================================|
16  C     | A procedure called EXTERNAL_FORCING_S is called from     |  C     | A procedure called EXTERNAL_FORCING_S is called from     |
17  C     | here. These procedures can be used to add per problem    |  C     | here. These procedures can be used to add per problem    |
18  C     | fresh water flux source terms.                           |  C     | E-P  flux source terms.                                  |
19  C     | Note: Although it is slightly counter-intuitive the      |  C     | Note: Although it is slightly counter-intuitive the      |
20  C     |       EXTERNAL_FORCING routine is not the place to put   |  C     |       EXTERNAL_FORCING routine is not the place to put   |
21  C     |       file I/O. Instead files that are required to       |  C     |       file I/O. Instead files that are required to       |
# Line 40  C     == GLobal variables == Line 41  C     == GLobal variables ==
41  #include "DYNVARS.h"  #include "DYNVARS.h"
42  #include "EEPARAMS.h"  #include "EEPARAMS.h"
43  #include "PARAMS.h"  #include "PARAMS.h"
44  #include "GRID.h"  #include "GAD.h"
45    
46  C     == Routine arguments ==  C     == Routine arguments ==
47  C     fZon    - Work array for flux of temperature in the east-west  C     fVerS   - Flux of salt (S) in the vertical
 C               direction at the west face of a cell.  
 C     fMer    - Work array for flux of temperature in the north-south  
 C               direction at the south face of a cell.  
 C     fVerS   - Flux of salinity (S) in the vertical  
48  C               direction at the upper(U) and lower(D) faces of a cell.  C               direction at the upper(U) and lower(D) faces of a cell.
49  C     maskUp  - Land mask used to denote base of the domain.  C     maskUp  - Land mask used to denote base of the domain.
50  C     xA      - Tracer cell face area normal to X  C     xA      - Tracer cell face area normal to X
51  C     yA      - Tracer cell face area normal to X  C     yA      - Tracer cell face area normal to X
52  C     uTrans  - Zonal volume transport through cell face  C     uTrans  - Zonal volume transport through cell face
53  C     vTrans  - Meridional volume transport through cell face  C     vTrans  - Meridional volume transport through cell face
54  C     wTrans  - Vertical volume transport through cell face  C     rTrans  - Vertical volume transport through cell face
 C     af      - Advective flux component work array  
 C     df      - Diffusive flux component work array  
55  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
56  C                                      results will be set.  C                                      results will be set.
57  C     myThid - Instance number for this innvocation of CALC_GS  C     myThid - Instance number for this innvocation of CALC_GT
       _RL fZon  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
       _RL fMer  (1-OLx:sNx+OLx,1-OLy:sNy+OLy)  
58        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)        _RL fVerS (1-OLx:sNx+OLx,1-OLy:sNy+OLy,2)
59        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS xA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS yA    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL uTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
62        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL vTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63        _RL wTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL rTrans(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
64        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RS maskUp(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
65        _RL af    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL KappaRS(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
66        _RL df    (1-OLx:sNx+OLx,1-OLy:sNy+OLy)        INTEGER k,kUp,kDown,kM1
       INTEGER kUp,kDown,kM1  
67        INTEGER bi,bj,iMin,iMax,jMin,jMax        INTEGER bi,bj,iMin,iMax,jMin,jMax
68          _RL     myTime
69          INTEGER myIter
70        INTEGER myThid        INTEGER myThid
 CEndOfInterface  
71    
72  C     == Local variables ==  C     == Local variables ==
 C     I, J, K - Loop counters  
       INTEGER i,j,k  
       INTEGER afFacS, dfFacS  
   
       afFacS = 1. _d 0  
       dfFacS = 1. _d 0  
   
 C---  
 C---  Calculate advective and diffusive fluxes between cells.  
 C---  
   
 C--   Zonal flux (fZon is at west face of "salt" cell)  
 C     Advective component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   uTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i-1,j,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Diffusive component of zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) =  
      &   -diffKhS*xA(i,j)*rdxC(i,j,bi,bj)  
      &   *(salt(i,j,k,bi,bj)-salt(i-1,j,k,bi,bj))  
        ENDDO  
       ENDDO  
 C     Net zonal flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fZon(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Meridional flux (fMer is at south face of "salt" cell)  
 C     Advective component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
 C       Advective component of meridional flux  
         af(i,j) =  
      &   vTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j-1,k,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Diffusive component of meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) =  
      &   -diffKhS*yA(i,j)*rdyC(i,j,bi,bj)  
      &   *(salt(i,j,k,bi,bj)-salt(i,j-1,k,bi,bj))  
        ENDDO  
       ENDDO  
 C     Net meridional flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fMer(i,j) = afFacS*af(i,j) + dfFacS*df(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Vertical flux (fVerS) above  
 C     Note: For K=1 then KM1=1 this gives a dS/dz = 0 upper  
 C           boundary condition.  
 C     Advective component of vertical flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         af(i,j) =  
      &   wTrans(i,j)*(salt(i,j,k,bi,bj)+salt(i,j,kM1,bi,bj))*0.5 _d 0  
        ENDDO  
       ENDDO  
 C     Diffusive component of vertical flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         df(i,j) =  
      &   -diffKzS*zA(i,j,bi,bj)*rdzC(k)  
      &   *(salt(i,j,kM1,bi,bj)-salt(i,j,k,bi,bj))  
        ENDDO  
       ENDDO  
 C     Net vertical flux  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         fVerS(i,j,kUp) = (afFacS*af(i,j) + dfFacS*df(i,j))*maskUp(i,j)  
        ENDDO  
       ENDDO  
   
 C--   Tendency is minus divergence of the fluxes.  
 C     Note. Tendency terms will only be correct for range  
 C           i=iMin+1:iMax-1, j=jMin+1:jMax-1. Edge points  
 C           will contain valid floating point numbers but  
 C           they are not algorithmically correct. These points  
 C           are not used.  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
         gS(i,j,k,bi,bj)=  
      &   -rHFacC(i,j,k,bi,bj)*rdzF(k)*rDxF(i,j,bi,bj)*rDyF(i,j,bi,bj)  
      &   *(  
      &    +( fZon(i+1,j)-fZon(i,j) )  
      &    +( fMer(i,j+1)-fMer(i,j) )  
      &    +( fVerS(i,j,kUp)-fVerS(i,j,kDown) )  
      &    )  
        ENDDO  
       ENDDO  
73    
74  C--   External haline forcing term(s)  #ifdef ALLOW_AUTODIFF_TAMC
75    C--   only the kUp part of fverS is set in this subroutine
76    C--   the kDown is still required
77          fVerS(1,1,kDown) = fVerS(1,1,kDown)
78    #endif
79    
80          CALL GAD_CALC_RHS(
81         I           bi,bj,iMin,iMax,jMin,jMax,k,kM1,kUp,kDown,
82         I           xA,yA,uTrans,vTrans,rTrans,maskUp,
83         I           diffKhS, diffK4S, KappaRS, Salt,
84         I           GAD_SALINITY, saltAdvScheme,
85         U           fVerS, gS,
86         I           myThid )
87    
88    C--   External forcing term(s)
89          CALL EXTERNAL_FORCING_S(
90         I     iMin,iMax,jMin,jMax,bi,bj,k,
91         I     myTime,myThid)
92    
93          IF ( saltAdvScheme.EQ.ENUM_CENTERED_2ND
94         & .OR.saltAdvScheme.EQ.ENUM_UPWIND_3RD
95         & .OR.saltAdvScheme.EQ.ENUM_CENTERED_4TH ) THEN
96            CALL ADAMS_BASHFORTH2(
97         I                        bi, bj, K,
98         U                        gS, gSnm1,
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                          gS,
107         I                          myThid )
108          ENDIF
109    #endif /* NONLIN_FRSURF */
110    
111        RETURN        RETURN
112        END        END

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.31

  ViewVC Help
Powered by ViewVC 1.1.22