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

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

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


Revision 1.7 - (hide annotations) (download)
Wed Apr 27 22:09:13 2016 UTC (8 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65w, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.6: +2 -2 lines
fix missing dPhiNH (substracted from phi_nh) for the case: selectP_inEOS_Zc=3

1 jmc 1.7 C $Header: /u/gcmpack/MITgcm/model/src/pressure_for_eos.F,v 1.6 2016/03/10 20:54:57 jmc Exp $
2 jmc 1.1 C $Name: $
3     #include "CPP_OPTIONS.h"
4    
5     CBOP
6     C !ROUTINE: PRESSURE_FOR_EOS
7     C !INTERFACE:
8 jmc 1.4 SUBROUTINE PRESSURE_FOR_EOS(
9 jmc 1.1 I bi, bj, iMin, iMax, jMin, jMax, k,
10     O locPres,
11     I myThid )
12     C !DESCRIPTION: \bv
13     C *==========================================================*
14 jmc 1.4 C | SUBROUTINE PRESSURE_FOR_EOS
15     C | o Provide a local copy of the total pressure
16 jmc 1.1 C | at cell center (level k) for use in EOS funct. of P
17     C *==========================================================*
18     C \ev
19    
20     C !USES:
21    
22     IMPLICIT NONE
23     C == Global variables ==
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "GRID.h"
28     #include "DYNVARS.h"
29 jmc 1.6 #ifdef ALLOW_NONHYDROSTATIC
30     # include "NH_VARS.h"
31     #endif /* ALLOW_NONHYDROSTATIC */
32 jmc 1.1
33     C !INPUT/OUTPUT PARAMETERS:
34     C == Routine arguments ==
35     C bi,bj, k :: tile and level indices
36     C iMin,iMax,jMin,jMax :: computational domain
37     C myThid - Thread number for this instance of the routine.
38     INTEGER bi, bj, k
39     INTEGER iMin,iMax,jMin,jMax
40     _RL locPres(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
41     INTEGER myThid
42    
43     C !LOCAL VARIABLES:
44     C == Local variables ==
45     C i,j :: loop index
46     INTEGER i,j
47     CEOP
48    
49     C
50     C provide the pressure for use in the equation of state
51     C
52 jmc 1.2 IF ( usingZCoords ) THEN
53 jmc 1.1 C in Z coordinates the pressure is rho0 * (hydrostatic) Potential
54 jmc 1.6 #ifdef ALLOW_NONHYDROSTATIC
55     IF ( selectP_inEOS_Zc.EQ.3 ) THEN
56     C- use full (hydrostatic+non-hydrostatic) dynamical pressure:
57     DO j=1-OLy,sNy+OLy
58     DO i=1-OLx,sNx+OLx
59     locPres(i,j) = rhoConst*(
60     & totPhiHyd(i,j,k,bi,bj)
61 jmc 1.7 & +( phi_nh(i,j,k,bi,bj) - dPhiNH(i,j,bi,bj) )
62 jmc 1.6 & + phiRef(2*k) )
63     c & *maskC(i,j,k,bi,bj)
64     ENDDO
65     ENDDO
66     ELSEIF ( selectP_inEOS_Zc.EQ.2 ) THEN
67     #else /* ALLOW_NONHYDROSTATIC */
68     IF ( selectP_inEOS_Zc.EQ.2 ) THEN
69     #endif /* ALLOW_NONHYDROSTATIC */
70     C- use hydrostatic dynamical pressure:
71 jmc 1.1 C----------
72     C NOTE: For now, totPhiHyd only contains the Potential anomaly
73 jmc 1.6 C since PhiRef has not (yet) been added in S/R DIAGS_PHI_HYD
74 jmc 1.1 C----------
75 jmc 1.5 DO j=1-OLy,sNy+OLy
76     DO i=1-OLx,sNx+OLx
77 jmc 1.1 locPres(i,j) = rhoConst*(
78     & totPhiHyd(i,j,k,bi,bj)
79 jmc 1.6 & + phiRef(2*k) )
80 jmc 1.4 c & *maskC(i,j,k,bi,bj)
81 jmc 1.1 ENDDO
82     ENDDO
83 jmc 1.6 c ELSEIF ( selectP_inEOS_Zc.EQ.1 ) THEN
84     C note: for the case selectP_inEOS_Zc=0, also use pRef4EOS (set to
85     C rhoConst*phiRef(2*k) ) to reproduce same previous machine truncation
86     ELSEIF ( selectP_inEOS_Zc.LE.1 ) THEN
87     C- use horizontally uniform reference pressure pRef
88     C (solution of: pRef = integral{-g*rho(Tref,Sref,pRef)*dz} )
89     DO j=1-OLy,sNy+OLy
90     DO i=1-OLx,sNx+OLx
91     locPres(i,j) = pRef4EOS(k)
92     c & *maskC(i,j,k,bi,bj)
93     ENDDO
94     ENDDO
95 jmc 1.1 ELSE
96 jmc 1.6 C- simplest case: -g*rhoConst*z
97 jmc 1.5 DO j=1-OLy,sNy+OLy
98     DO i=1-OLx,sNx+OLx
99 jmc 1.6 locPres(i,j) = rhoConst*phiRef(2*k)
100 jmc 1.4 c & *maskC(i,j,k,bi,bj)
101 jmc 1.1 ENDDO
102     ENDDO
103     ENDIF
104 jmc 1.2 ELSEIF ( usingPCoords ) THEN
105 jmc 1.1 C in P coordinates the pressure is just the coordinate of
106     C the tracer point
107 jmc 1.5 DO j=1-OLy,sNy+OLy
108     DO i=1-OLx,sNx+OLx
109 jmc 1.1 locPres(i,j) = rC(k)
110 jmc 1.4 c & * maskC(i,j,k,bi,bj)
111 jmc 1.1 ENDDO
112     ENDDO
113     ENDIF
114    
115 jmc 1.4 RETURN
116 jmc 1.1 END

  ViewVC Help
Powered by ViewVC 1.1.22