Back to home page

MITgcm

 
 

    


File indexing completed on 2020-04-27 05:10:45 UTC

view on githubraw file Latest commit 533b1afc on 2020-03-10 22:11:22 UTC
6ac14281aa Jean*0001 #include "CPP_OPTIONS.h"
                0002 
                0003 CBOP
                0004 C     !ROUTINE: PRESSURE_FOR_EOS
                0005 C     !INTERFACE:
8b745dc884 Jean*0006       SUBROUTINE PRESSURE_FOR_EOS(
533b1afce7 Jean*0007      I        bi, bj, iMin, iMax, jMin, jMax,  k, dpRef,
6ac14281aa Jean*0008      O        locPres,
                0009      I        myThid )
                0010 C     !DESCRIPTION: \bv
                0011 C     *==========================================================*
8b745dc884 Jean*0012 C     | SUBROUTINE PRESSURE_FOR_EOS
                0013 C     | o Provide a local copy of the total pressure
6ac14281aa Jean*0014 C     |   at cell center (level k) for use in EOS funct. of P
533b1afce7 Jean*0015 C     | Note: Since most seawater EOS are formulated as function
                0016 C     |   of pressure anomaly relative to a reference P, this
                0017 C     |   S/R allows to account for this reference Pressure (or
                0018 C     |   different ref P) by adding a pressure shift "dpRef"
                0019 C     |   to the output pressure.
6ac14281aa Jean*0020 C     *==========================================================*
                0021 C     \ev
                0022 
                0023 C     !USES:
                0024 
                0025       IMPLICIT NONE
                0026 C     == Global variables ==
                0027 #include "SIZE.h"
                0028 #include "EEPARAMS.h"
                0029 #include "PARAMS.h"
                0030 #include "GRID.h"
                0031 #include "DYNVARS.h"
759f945c40 Jean*0032 #ifdef ALLOW_NONHYDROSTATIC
                0033 # include "NH_VARS.h"
                0034 #endif /* ALLOW_NONHYDROSTATIC */
6ac14281aa Jean*0035 
                0036 C     !INPUT/OUTPUT PARAMETERS:
                0037 C     == Routine arguments ==
533b1afce7 Jean*0038 C     bi, bj, k :: tile and level indices
                0039 C     iMin,iMax :: computational domain, first index range
                0040 C     jMin,jMax :: computational domain, second index range
                0041 C     dpRef     :: shift applied to output pressure [Pa]
                0042 C     locPres   :: total pressure for use in EOS [Pa]
                0043 C     myThid    :: my Thread Id number
6ac14281aa Jean*0044       INTEGER bi, bj, k
                0045       INTEGER iMin,iMax,jMin,jMax
533b1afce7 Jean*0046       _RL dpRef
6ac14281aa Jean*0047       _RL locPres(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
                0048       INTEGER myThid
                0049 
                0050 C     !LOCAL VARIABLES:
                0051 C     == Local variables ==
                0052 C     i,j :: loop index
                0053       INTEGER  i,j
                0054 CEOP
                0055 
533b1afce7 Jean*0056 C     Provide the pressure for use in the equation of state
                0057 
9669509dca Jean*0058       IF ( usingZCoords ) THEN
6ac14281aa Jean*0059 C     in Z coordinates the pressure is rho0 * (hydrostatic) Potential
759f945c40 Jean*0060 #ifdef ALLOW_NONHYDROSTATIC
                0061        IF ( selectP_inEOS_Zc.EQ.3 ) THEN
                0062 C-     use full (hydrostatic+non-hydrostatic) dynamical pressure:
                0063          DO j=1-OLy,sNy+OLy
                0064           DO i=1-OLx,sNx+OLx
                0065             locPres(i,j) = rhoConst*(
                0066      &                   totPhiHyd(i,j,k,bi,bj)
7fc53bea2b Jean*0067      &                 +( phi_nh(i,j,k,bi,bj) - dPhiNH(i,j,bi,bj) )
533b1afce7 Jean*0068      &                 + phiRef(2*k) ) + dpRef
759f945c40 Jean*0069           ENDDO
                0070          ENDDO
                0071        ELSEIF ( selectP_inEOS_Zc.EQ.2 ) THEN
                0072 #else /* ALLOW_NONHYDROSTATIC */
                0073        IF     ( selectP_inEOS_Zc.EQ.2 ) THEN
                0074 #endif /* ALLOW_NONHYDROSTATIC */
                0075 C-     use hydrostatic dynamical pressure:
6ac14281aa Jean*0076 C----------
                0077 C     NOTE: For now, totPhiHyd only contains the Potential anomaly
759f945c40 Jean*0078 C           since PhiRef has not (yet) been added in S/R DIAGS_PHI_HYD
6ac14281aa Jean*0079 C----------
901f12b7bc Jean*0080          DO j=1-OLy,sNy+OLy
                0081           DO i=1-OLx,sNx+OLx
6ac14281aa Jean*0082             locPres(i,j) = rhoConst*(
                0083      &                   totPhiHyd(i,j,k,bi,bj)
533b1afce7 Jean*0084      &                 + phiRef(2*k) ) + dpRef
6ac14281aa Jean*0085           ENDDO
                0086          ENDDO
759f945c40 Jean*0087 c      ELSEIF ( selectP_inEOS_Zc.EQ.1 ) THEN
                0088 C note: for the case selectP_inEOS_Zc=0, also use pRef4EOS (set to
                0089 C       rhoConst*phiRef(2*k) ) to reproduce same previous machine truncation
                0090        ELSEIF ( selectP_inEOS_Zc.LE.1 ) THEN
                0091 C-     use horizontally uniform reference pressure pRef
                0092 C      (solution of: pRef = integral{-g*rho(Tref,Sref,pRef)*dz} )
                0093          DO j=1-OLy,sNy+OLy
                0094           DO i=1-OLx,sNx+OLx
533b1afce7 Jean*0095             locPres(i,j) = pRef4EOS(k) + dpRef
759f945c40 Jean*0096           ENDDO
                0097          ENDDO
6ac14281aa Jean*0098        ELSE
759f945c40 Jean*0099 C-     simplest case: -g*rhoConst*z
901f12b7bc Jean*0100          DO j=1-OLy,sNy+OLy
                0101           DO i=1-OLx,sNx+OLx
533b1afce7 Jean*0102             locPres(i,j) = rhoConst*phiRef(2*k) + dpRef
6ac14281aa Jean*0103           ENDDO
                0104          ENDDO
                0105        ENDIF
9669509dca Jean*0106       ELSEIF ( usingPCoords ) THEN
6ac14281aa Jean*0107 C     in P coordinates the pressure is just the coordinate of
                0108 C     the tracer point
901f12b7bc Jean*0109          DO j=1-OLy,sNy+OLy
                0110           DO i=1-OLx,sNx+OLx
533b1afce7 Jean*0111             locPres(i,j) = rC(k) + dpRef
6ac14281aa Jean*0112           ENDDO
                0113          ENDDO
                0114       ENDIF
                0115 
8b745dc884 Jean*0116       RETURN
6ac14281aa Jean*0117       END