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

Contents 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.1 - (show annotations) (download)
Fri Jan 12 21:02:46 2001 UTC (24 years, 6 months ago) by adcroft
Branch: branch-atmos-merge
CVS Tags: branch-atmos-merge-phase4
Changes since 1.8: +93 -38 lines
Re-wrote calc_phi_hyd()
 - use theta and salt as arguments (necessary for staggered time-step)
 - calls find_rho() from inside
 - find_rho() also takes theta,salt as arguments
 - uses different formulation for 'OCEANIC' and 'ATMOSPHERIC' modes
 - "finite volume" (non-energy conserving) form supplied in comments

1 C $Header: /u/gcmpack/models/MITgcmUV/model/src/calc_phi_hyd.F,v 1.8 2000/11/13 16:32:57 heimbach 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
53 IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
54
55 dRloc=drC(k)
56 IF (k.EQ.1) dRloc=drF(1)
57 IF (k.EQ.Nr) THEN
58 dRlocKp1=0.
59 ELSE
60 dRlocKp1=drC(k+1)
61 ENDIF
62
63 C-- If this is the top layer we impose the boundary condition
64 C P(z=eta) = P(atmospheric_loading)
65 IF (k.EQ.1) THEN
66 DO j=jMin,jMax
67 DO i=iMin,iMax
68 C *NOTE* The loading should go here but has not been implemented yet
69 phiHydInterface(i,j)=0.
70 phiHyd(i,j,k)=0.
71 ENDDO
72 ENDDO
73 ENDIF
74
75 C Calculate density
76 CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,
77 & theta, salt,
78 & alphaRho, myThid)
79
80 C Hydrostatic pressure at cell centers
81 DO j=jMin,jMax
82 DO i=iMin,iMax
83 #ifdef ALLOW_AUTODIFF_TAMC
84 Is this directive correct or even necessary in this new code?
85 CADJ GENERAL
86 #endif
87 C This discretization is the "finite volume" form
88 C which has not been used to date since it does not
89 C conserve KE+PE exactly even though it is more natural
90 C
91 C phiHyd(i,j,k)=phiHydInterface(i,j)+
92 C & 0.5*drF(K)*gravity*alphaRho(i,j)
93 C
94 C This discretization is the "energy conserving" form
95 C which has been used since at least Adcroft et al., MWR 1997
96 C
97 phiHyd(i,j,k)=phiHyd(i,j,k)+
98 & 0.5*dRloc*gravity*alphaRho(i,j)
99 phiHyd(i,j,k+1)=phiHyd(i,j,k)+
100 & 0.5*dRlocKp1*gravity*alphaRho(i,j)
101 ENDDO
102 ENDDO
103
104 C Hydrostatic pressure at interface below
105 DO j=jMin,jMax
106 DO i=iMin,iMax
107 phiHydInterface(i,j)=phiHydInterface(i,j)+
108 & drF(K)*gravity*alphaRho(i,j)
109 ENDDO
110 ENDDO
111
112 ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
113
114 ELSE
115 STOP 'CALC_PHI_HYD: We should never reach this point!'
116 ENDIF
117
118 #endif
119
120 return
121 end

  ViewVC Help
Powered by ViewVC 1.1.22