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

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

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


Revision 1.8.2.4 - (hide annotations) (download)
Thu Jan 25 19:43:32 2001 UTC (24 years, 5 months ago) by adcroft
Branch: branch-atmos-merge
Changes since 1.8.2.3: +8 -10 lines
o Removed array phiHydInterface. Why have more arguments than are necessary.
It made the "finite volume" integration easier but wasn't used for
the default energy conserving method. The fv is still available in
comments but has been coded without the phiHydInterface array.
o Put a safety "IF" in front of k+1 references.

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

  ViewVC Help
Powered by ViewVC 1.1.22