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

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

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

revision 1.8 by heimbach, Mon Nov 13 16:32:57 2000 UTC revision 1.9 by adcroft, Fri Feb 2 21:04:47 2001 UTC
# Line 2  C $Header$ Line 2  C $Header$
2    
3  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
4    
5        SUBROUTINE CALC_PHI_HYD( bi, bj, iMin, iMax, jMin, jMax, K,        SUBROUTINE CALC_PHI_HYD(
6       I    buoyKM1, buoyKP1, phiHyd, myThid)       I                         bi, bj, iMin, iMax, jMin, jMax, K,
7         I                         theta, salt,
8         U                         phiHyd,
9         I                         myThid)
10  C     /==========================================================\  C     /==========================================================\
11  C     | SUBROUTINE CALC_PHI_HYD                                  |  C     | SUBROUTINE CALC_PHI_HYD                                  |
12  C     | o Integrate the hydrostatic relation to find phiHyd.     |  C     | o Integrate the hydrostatic relation to find phiHyd.     |
13  C     |                                                          |  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     |   phiHyd(i,j,k) 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     |   phiHyd(i,j,k+1) is the hydrostatic pressure/geop.      |
29    C     |                 at cell the interface k+1 (w point below)|
30    C     |                                                          |
31  C     \==========================================================/  C     \==========================================================/
32        IMPLICIT NONE        IMPLICIT NONE
33  C     == Global variables ==  C     == Global variables ==
34  #include "SIZE.h"  #include "SIZE.h"
 #include "DYNVARS.h"  
35  #include "GRID.h"  #include "GRID.h"
36  #include "EEPARAMS.h"  #include "EEPARAMS.h"
37  #include "PARAMS.h"  #include "PARAMS.h"
38  C     == Routine arguments ==  C     == Routine arguments ==
39        INTEGER bi,bj,iMin,iMax,jMin,jMax,K        INTEGER bi,bj,iMin,iMax,jMin,jMax,K
40        _RL buoyKM1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
41        _RL buoyKP1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _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)        _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
43        integer myThid        INTEGER myThid
 C     == Local variables ==  
       INTEGER i,j,Km1  
       _RL halfLayer  
       _RL gamma  
44    
45  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
46    
47        if (K.eq.1) then  C     == Local variables ==
48         Km1=1        INTEGER i,j
49         halfLayer=0.5 _d 0        _RL alphaRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50        else        _RL dRloc,dRlocKp1
51         Km1=K-1        _RL ddRm1, ddRp1, ddRm, ddRp
52         halfLayer=1.0 _d 0        _RL atm_cp, atm_kappa, atm_po
53        endif  
54          IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
55  C--   Scale factor for hydrostatic relation except for ocean in  C       This is the hydrostatic pressure calculation for the Ocean
56  C--   pressure coords.  C       which uses the FIND_RHO() routine to calculate density
57        gamma = 1. _d 0  C       before integrating g*rho over the current layer/interface
58  C--   Scale factor for hydrostatic relation for ocean in pressure  
59  C--   coords.          dRloc=drC(k)
60        IF ( buoyancyRelation .EQ. 'OCEANIC' .AND. usingPCoords ) THEN          IF (k.EQ.1) dRloc=drF(1)
61         gamma = recip_Gravity*recip_rhoConst          IF (k.EQ.Nr) THEN
62        ENDIF            dRlocKp1=0.
63            ELSE
64  C--   Contribution to phiHyd(:,:,K) from buoy(:,:,K-1) + buoy(:,:,K)            dRlocKp1=drC(k+1)
65  C     (This is now the actual hydrostatic pressure|height at the T/S          ENDIF
66  C     points)  
67        DO j=jMin,jMax  C--     If this is the top layer we impose the boundary condition
68         DO i=iMin,iMax  C       P(z=eta) = P(atmospheric_loading)
69  #ifdef ALLOW_AUTODIFF_TAMC          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    #ifdef      ALLOW_AUTODIFF_TAMC
87                Is this directive correct or even necessary in this new code?
88  CADJ GENERAL  CADJ GENERAL
89  #endif  #endif      /* ALLOW_AUTODIFF_TAMC */
90          phiHyd(i,j,K)=phiHyd(i,j,Km1)-rhoConst*halfLayer  
91       &  *0.5 _d 0*( drF(Km1)+drF(K) )*gamma  C---------- This discretization is the "finite volume" form
92       &  *0.5 _d 0*( buoyKM1(i,j)+buoyKP1(i,j) )  C           which has not been used to date since it does not
93         ENDDO  C           conserve KE+PE exactly even though it is more natural
94        ENDDO  C
95    c           IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
96    c    &              drF(K)*gravity*alphaRho(i,j)
97    c           phiHyd(i,j,k)=phiHyd(i,j,k)+
98    c    &          0.5*drF(K)*gravity*alphaRho(i,j)
99    C-----------------------------------------------------------------------
100    
101    C---------- This discretization is the "energy conserving" form
102    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                IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
107         &          0.5*dRlocKp1*gravity*alphaRho(i,j)
108    C-----------------------------------------------------------------------
109              ENDDO
110            ENDDO
111            
112    
113    
114    
115          ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
116    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    
120    C       Integrate d Phi / d pi
121    
122    C *NOTE* These constants should be in the data file and PARAMS.h
123            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                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         &          -ddRp*(theta(I,J,K,bi,bj)-tRef(K))
140    C-----------------------------------------------------------------------
141               ENDDO
142              ENDDO
143            ELSE
144    
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              ddRp1=atm_cp*( ((rC( K )/atm_po)**atm_kappa)
160         &                  -((rC(K-1)/atm_po)**atm_kappa) )*0.5
161              ddRm1=ddRp1
162    C-----------------------------------------------------------------------
163    
164              DO j=jMin,jMax
165                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 (atmos-exact) 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)-2.*tRef(K))
176                ENDDO
177              ENDDO
178            ENDIF
179    
180    
181          ELSE
182            STOP 'CALC_PHI_HYD: We should never reach this point!'
183          ENDIF
184    
185  #endif  #endif
186    

Legend:
Removed from v.1.8  
changed lines
  Added in v.1.9

  ViewVC Help
Powered by ViewVC 1.1.22