1 |
C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_phi_hyd.F,v 1.8.2.2 2001/01/17 18:53:34 jmc Exp $ |
2 |
|
3 |
#include "CPP_OPTIONS.h" |
4 |
|
5 |
SUBROUTINE CALC_PHI_HYD( |
6 |
I bi, bj, iMin, iMax, jMin, jMax, K, |
7 |
I theta, salt, |
8 |
U phiHyd, phiHydInterface, |
9 |
I myThid) |
10 |
C /==========================================================\ |
11 |
C | SUBROUTINE CALC_PHI_HYD | |
12 |
C | o Integrate the hydrostatic relation to find phiHyd. | |
13 |
C | | |
14 |
C | On entry: | |
15 |
C | theta,salt are the current thermodynamics quantities| |
16 |
C | (unchanged on exit) | |
17 |
C | phiHyd(i,j,1:k-1) is the hydrostatic pressure/geopot. | |
18 |
C | at cell centers (tracer points) | |
19 |
C | - 1:k-1 layers are valid | |
20 |
C | - k:Nr layers are invalid | |
21 |
C | phiHydInterface(i,j) is the hydrostatic pressure/geop. | |
22 |
C | at cell the interface k (w point above) | |
23 |
C | On exit: | |
24 |
C | phiHyd(i,j,1:k) is the hydrostatic pressure/geopot. | |
25 |
C | at cell centers (tracer points) | |
26 |
C | - 1:k layers are valid | |
27 |
C | - k+1:Nr layers are invalid | |
28 |
C | phiHydInterface(i,j) is the hydrostatic pressure/geop. | |
29 |
C | at cell the interface k+1 (w point below)| |
30 |
C | | |
31 |
C \==========================================================/ |
32 |
IMPLICIT NONE |
33 |
C == Global variables == |
34 |
#include "SIZE.h" |
35 |
#include "GRID.h" |
36 |
#include "EEPARAMS.h" |
37 |
#include "PARAMS.h" |
38 |
C == Routine arguments == |
39 |
INTEGER bi,bj,iMin,iMax,jMin,jMax,K |
40 |
_RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy) |
41 |
_RL salt(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy) |
42 |
_RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr) |
43 |
_RL phiHydInterface(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
44 |
INTEGER myThid |
45 |
|
46 |
#ifdef INCLUDE_PHIHYD_CALCULATION_CODE |
47 |
|
48 |
C == Local variables == |
49 |
INTEGER i,j |
50 |
_RL alphaRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy) |
51 |
_RL dRloc,dRlocKp1 |
52 |
_RL ddRm1, ddRp1, ddRm, ddRp |
53 |
_RL atm_cp, atm_kappa, atm_po |
54 |
|
55 |
IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN |
56 |
C This is the hydrostatic pressure calculation for the Ocean |
57 |
C which uses the FIND_RHO() routine to calculate density |
58 |
C before integrating g*rho over the current layer/interface |
59 |
|
60 |
dRloc=drC(k) |
61 |
IF (k.EQ.1) dRloc=drF(1) |
62 |
IF (k.EQ.Nr) THEN |
63 |
dRlocKp1=0. |
64 |
ELSE |
65 |
dRlocKp1=drC(k+1) |
66 |
ENDIF |
67 |
|
68 |
C-- If this is the top layer we impose the boundary condition |
69 |
C P(z=eta) = P(atmospheric_loading) |
70 |
IF (k.EQ.1) THEN |
71 |
DO j=jMin,jMax |
72 |
DO i=iMin,iMax |
73 |
C *NOTE* The loading should go here but has not been implemented yet |
74 |
phiHydInterface(i,j)=0. |
75 |
phiHyd(i,j,k)=0. |
76 |
ENDDO |
77 |
ENDDO |
78 |
ENDIF |
79 |
|
80 |
C Calculate density |
81 |
CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k, eosType, |
82 |
& theta, salt, |
83 |
& alphaRho, myThid) |
84 |
|
85 |
C Hydrostatic pressure at cell centers |
86 |
DO j=jMin,jMax |
87 |
DO i=iMin,iMax |
88 |
#ifdef ALLOW_AUTODIFF_TAMC |
89 |
Is this directive correct or even necessary in this new code? |
90 |
CADJ GENERAL |
91 |
#endif /* ALLOW_AUTODIFF_TAMC */ |
92 |
|
93 |
C---------- This discretization is the "finite volume" form |
94 |
C which has not been used to date since it does not |
95 |
C conserve KE+PE exactly even though it is more natural |
96 |
C |
97 |
c phiHyd(i,j,k)=phiHydInterface(i,j)+ |
98 |
c & 0.5*drF(K)*gravity*alphaRho(i,j) |
99 |
c phiHydInterface(i,j)=phiHydInterface(i,j)+ |
100 |
c & drF(K)*gravity*alphaRho(i,j) |
101 |
C----------------------------------------------------------------------- |
102 |
|
103 |
C---------- This discretization is the "energy conserving" form |
104 |
C which has been used since at least Adcroft et al., MWR 1997 |
105 |
C |
106 |
phiHyd(i,j,k)=phiHyd(i,j,k)+ |
107 |
& 0.5*dRloc*gravity*alphaRho(i,j) |
108 |
phiHyd(i,j,k+1)=phiHyd(i,j,k)+ |
109 |
& 0.5*dRlocKp1*gravity*alphaRho(i,j) |
110 |
C----------------------------------------------------------------------- |
111 |
ENDDO |
112 |
ENDDO |
113 |
|
114 |
|
115 |
|
116 |
|
117 |
ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN |
118 |
C This is the hydrostatic geopotential calculation for the Atmosphere |
119 |
C The ideal gas law is used implicitly here rather than calculating |
120 |
C the specific volume, analogous to the oceanic case. |
121 |
|
122 |
C Integrate d Phi / d pi |
123 |
|
124 |
C *NOTE* These constants should be in the data file and PARAMS.h |
125 |
atm_cp=1004. _d 0 |
126 |
atm_kappa=2. _d 0/7. _d 0 |
127 |
atm_po=1. _d 5 |
128 |
IF (K.EQ.1) THEN |
129 |
ddRp1=atm_cp*( ((rC(K)/atm_po)**atm_kappa) |
130 |
& -((rF(K)/atm_po)**atm_kappa) ) |
131 |
DO j=jMin,jMax |
132 |
DO i=iMin,iMax |
133 |
ddRp=ddRp1 |
134 |
IF (hFacC(I,J, K ,bi,bj).EQ.0.) ddRp=0. |
135 |
C------------ The integration for the first level phi(k=1) is the |
136 |
C same for both the "finite volume" and energy conserving |
137 |
C methods. |
138 |
C *NOTE* The geopotential boundary condition should go |
139 |
C here but has not been implemented yet |
140 |
phiHyd(i,j,K)=0. |
141 |
& -ddRp*(theta(I,J,K,bi,bj)-tRef(K)) |
142 |
C----------------------------------------------------------------------- |
143 |
ENDDO |
144 |
ENDDO |
145 |
ELSE |
146 |
|
147 |
C-------- This discretization is the "finite volume" form which |
148 |
C integrates the hydrostatic equation of each half/sub-layer. |
149 |
C This seems most natural and could easily allow for lopped cells |
150 |
C by replacing rF(K) with the height of the surface (not implemented). |
151 |
C in the lower layers (e.g. at k=1). |
152 |
C |
153 |
c ddRm1=atm_cp*( ((rF( K )/atm_po)**atm_kappa) |
154 |
c & -((rC(K-1)/atm_po)**atm_kappa) ) |
155 |
c ddRp1=atm_cp*( ((rC( K )/atm_po)**atm_kappa) |
156 |
c & -((rF( K )/atm_po)**atm_kappa) ) |
157 |
C----------------------------------------------------------------------- |
158 |
|
159 |
|
160 |
C-------- This discretization is the energy conserving form |
161 |
ddRp1=atm_cp*( ((rC( K )/atm_po)**atm_kappa) |
162 |
& -((rC(K-1)/atm_po)**atm_kappa) )*0.5 |
163 |
ddRm1=ddRp1 |
164 |
C----------------------------------------------------------------------- |
165 |
|
166 |
DO j=jMin,jMax |
167 |
DO i=iMin,iMax |
168 |
ddRp=ddRp1 |
169 |
ddRm=ddRm1 |
170 |
IF (hFacC(I,J, K ,bi,bj).EQ.0.) ddRp=0. |
171 |
IF (hFacC(I,J,K-1,bi,bj).EQ.0.) ddRm=0. |
172 |
phiHyd(i,j,K)=phiHyd(i,j,K-1) |
173 |
& -( ddRm*(theta(I,J,K-1,bi,bj)-tRef(K-1)) |
174 |
& +ddRp*(theta(I,J, K ,bi,bj)-tRef( K )) ) |
175 |
C Old code bug looked like this |
176 |
Cold phiHyd(i,j,K)=phiHyd(i,j,K-1)-(ddRm1* |
177 |
Cold & (theta(I,J,K-1,bi,bj)+theta(I,J,K,bi,bj))-tRef(K)) |
178 |
ENDDO |
179 |
ENDDO |
180 |
ENDIF |
181 |
|
182 |
|
183 |
ELSE |
184 |
STOP 'CALC_PHI_HYD: We should never reach this point!' |
185 |
ENDIF |
186 |
|
187 |
#endif |
188 |
|
189 |
return |
190 |
end |