/[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.7 by heimbach, Fri Jun 9 02:45:04 2000 UTC revision 1.13 by heimbach, Mon May 14 21:51:24 2001 UTC
# Line 1  Line 1 
1  C $Header$  C $Header$
2    C $Name$
3    
4  #include "CPP_OPTIONS.h"  #include "CPP_OPTIONS.h"
5    
6        SUBROUTINE CALC_PHI_HYD( bi, bj, iMin, iMax, jMin, jMax, K,        SUBROUTINE CALC_PHI_HYD(
7       I    buoyKM1, buoyKP1, phiHyd, myThid)       I                         bi, bj, iMin, iMax, jMin, jMax, K,
8         I                         theta, salt,
9         U                         phiHyd,
10         I                         myThid)
11  C     /==========================================================\  C     /==========================================================\
12  C     | SUBROUTINE CALC_PHI_HYD                                  |  C     | SUBROUTINE CALC_PHI_HYD                                  |
13  C     | o Integrate the hydrostatic relation to find phiHyd.     |  C     | o Integrate the hydrostatic relation to find the Hydros. |
14    C     |    Potential (ocean: Pressure/rho ; atmos = geopotential)|
15    C     | On entry:                                                |
16    C     |   theta,salt    are the current thermodynamics quantities|
17    C     |                 (unchanged on exit)                      |
18    C     |   phiHyd(i,j,1:k-1) is the hydrostatic Potential         |
19    C     |                 at cell centers (tracer points)          |
20    C     |                 - 1:k-1 layers are valid                 |
21    C     |                 - k:Nr layers are invalid                |
22    C     |   phiHyd(i,j,k) is the hydrostatic Potential             |
23    C     |                 at cell the interface k (w point above)  |
24    C     | On exit:                                                 |
25    C     |   phiHyd(i,j,1:k) is the hydrostatic Potential           |
26    C     |                 at cell centers (tracer points)          |
27    C     |                 - 1:k layers are valid                   |
28    C     |                 - k+1:Nr layers are invalid              |
29    C     |   phiHyd(i,j,k+1) is the hydrostatic Potential (P/rho)   |
30    C     |                 at cell the interface k+1 (w point below)|
31  C     |                                                          |  C     |                                                          |
32  C     \==========================================================/  C     \==========================================================/
33        IMPLICIT NONE        IMPLICIT NONE
34  C     == Global variables ==  C     == Global variables ==
35  #include "SIZE.h"  #include "SIZE.h"
 #include "DYNVARS.h"  
36  #include "GRID.h"  #include "GRID.h"
37  #include "EEPARAMS.h"  #include "EEPARAMS.h"
38  #include "PARAMS.h"  #include "PARAMS.h"
39    #ifdef ALLOW_AUTODIFF_TAMC
40    #include "tamc.h"
41    #include "tamc_keys.h"
42    #endif /* ALLOW_AUTODIFF_TAMC */
43    
44  C     == Routine arguments ==  C     == Routine arguments ==
45        INTEGER bi,bj,iMin,iMax,jMin,jMax,K        INTEGER bi,bj,iMin,iMax,jMin,jMax,K
46        _RL buoyKM1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL theta(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
47        _RL buoyKP1(1-OLx:sNx+OLx,1-OLy:sNy+OLy)        _RL salt(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
48        _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)        _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
49        integer myThid        INTEGER myThid
 C     == Local variables ==  
       INTEGER i,j,Km1  
       _RL halfLayer  
       _RL gamma  
50    
51  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
52    
53        if (K.eq.1) then  C     == Local variables ==
54         Km1=1        INTEGER i,j
55         halfLayer=0.5 _d 0        _RL alphaRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
56        else        _RL dRloc,dRlocKp1
57         Km1=K-1        _RL ddRm1, ddRp1, ddRm, ddRp
58         halfLayer=1.0 _d 0        _RL atm_cp, atm_kappa, atm_po
       endif  
   
 C--   Scale factor for hydrostatic relation except for ocean in  
 C--   pressure coords.  
       gamma = 1. _d 0  
 C--   Scale factor for hydrostatic relation for ocean in pressure  
 C--   coords.  
       IF ( buoyancyRelation .EQ. 'OCEANIC' .AND. usingPCoords ) THEN  
        gamma = recip_Gravity*recip_rhoConst  
       ENDIF  
59    
 C--   Contribution to phiHyd(:,:,K) from buoy(:,:,K-1) + buoy(:,:,K)  
 C     (This is now the actual hydrostatic pressure|height at the T/S  
 C     points)  
       DO j=jMin,jMax  
        DO i=iMin,iMax  
60  #ifdef ALLOW_AUTODIFF_TAMC  #ifdef ALLOW_AUTODIFF_TAMC
61              act1 = bi - myBxLo(myThid)
62              max1 = myBxHi(myThid) - myBxLo(myThid) + 1
63    
64              act2 = bj - myByLo(myThid)
65              max2 = myByHi(myThid) - myByLo(myThid) + 1
66    
67              act3 = myThid - 1
68              max3 = nTx*nTy
69    
70              act4 = ikey_dynamics - 1
71    
72              ikey = (act1 + 1) + act2*max1
73         &                      + act3*max1*max2
74         &                      + act4*max1*max2*max3
75    #endif /* ALLOW_AUTODIFF_TAMC */
76    
77          IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
78    C       This is the hydrostatic pressure calculation for the Ocean
79    C       which uses the FIND_RHO() routine to calculate density
80    C       before integrating g*rho over the current layer/interface
81    
82            dRloc=drC(k)
83            IF (k.EQ.1) dRloc=drF(1)
84            IF (k.EQ.Nr) THEN
85              dRlocKp1=0.
86            ELSE
87              dRlocKp1=drC(k+1)
88            ENDIF
89    
90    C--     If this is the top layer we impose the boundary condition
91    C       P(z=eta) = P(atmospheric_loading)
92            IF (k.EQ.1) THEN
93              DO j=jMin,jMax
94                DO i=iMin,iMax
95    C             *NOTE* The loading should go here but has not been implemented yet
96                  phiHyd(i,j,k)=0.
97                ENDDO
98              ENDDO
99            ENDIF
100    
101    C       Calculate density
102    #ifdef ALLOW_AUTODIFF_TAMC
103                kkey = (ikey-1)*Nr + k
104    CADJ STORE theta(:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
105    CADJ STORE salt (:,:,k,bi,bj) = comlev1_bibj_k, key=kkey, byte=isbyte
106    #endif /* ALLOW_AUTODIFF_TAMC */
107            CALL FIND_RHO( bi, bj, iMin, iMax, jMin, jMax, k, k, eosType,
108         &                 theta, salt,
109         &                 alphaRho, myThid)
110    
111    C       Hydrostatic pressure at cell centers
112            DO j=jMin,jMax
113              DO i=iMin,iMax
114    #ifdef      ALLOW_AUTODIFF_TAMC
115    c           Patrick, is this directive correct or even necessary in
116    c           this new code?
117    c           Yes, because of phiHyd(i,j,k+1)=phiHyd(i,j,k)+...
118    c           within the k-loop.
119  CADJ GENERAL  CADJ GENERAL
120  #endif  #endif      /* ALLOW_AUTODIFF_TAMC */
121          phiHyd(i,j,K)=phiHyd(i,j,Km1)-rhoConst*halfLayer  
122       &  *0.5 _d 0*( drF(Km1)+drF(K) )*gamma  C---------- This discretization is the "finite volume" form
123       &  *0.5 _d 0*( buoyKM1(i,j)+buoyKP1(i,j) )  C           which has not been used to date since it does not
124         ENDDO  C           conserve KE+PE exactly even though it is more natural
125        ENDDO  C
126    c           IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
127    c    &              drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
128    c           phiHyd(i,j,k)=phiHyd(i,j,k)+
129    c    &          0.5*drF(K)*gravity*alphaRho(i,j)*recip_rhoConst
130    C-----------------------------------------------------------------------
131    
132    C---------- This discretization is the "energy conserving" form
133    C           which has been used since at least Adcroft et al., MWR 1997
134    C
135                phiHyd(i,j,k)=phiHyd(i,j,k)+
136         &          0.5*dRloc*gravity*alphaRho(i,j)*recip_rhoConst
137                IF (k.LT.Nr) phiHyd(i,j,k+1)=phiHyd(i,j,k)+
138         &          0.5*dRlocKp1*gravity*alphaRho(i,j)*recip_rhoConst
139    C-----------------------------------------------------------------------
140              ENDDO
141            ENDDO
142            
143    
144    
145          ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
146    C       This is the hydrostatic geopotential calculation for the Atmosphere
147    C       The ideal gas law is used implicitly here rather than calculating
148    C       the specific volume, analogous to the oceanic case.
149    
150    C       Integrate d Phi / d pi
151    
152    C *NOTE* These constants should be in the data file and PARAMS.h
153            atm_cp=1004. _d 0
154            atm_kappa=2. _d 0/7. _d 0
155            atm_po=1. _d 5
156            IF (K.EQ.1) THEN
157              ddRp1=atm_cp*( ((rC(K)/atm_po)**atm_kappa)
158         &                  -((rF(K)/atm_po)**atm_kappa) )
159              DO j=jMin,jMax
160                DO i=iMin,iMax
161                  ddRp=ddRp1
162                  IF (hFacC(I,J, K ,bi,bj).EQ.0.) ddRp=0.
163    C------------ The integration for the first level phi(k=1) is the
164    C             same for both the "finite volume" and energy conserving
165    C             methods.
166    C             *NOTE* The geopotential boundary condition should go
167    C                    here but has not been implemented yet
168                  phiHyd(i,j,K)=0.
169         &          -ddRp*(theta(I,J,K,bi,bj)-tRef(K))
170    C-----------------------------------------------------------------------
171               ENDDO
172              ENDDO
173            ELSE
174    
175    C-------- This discretization is the "finite volume" form which
176    C         integrates the hydrostatic equation of each half/sub-layer.
177    C         This seems most natural and could easily allow for lopped cells
178    C         by replacing rF(K) with the height of the surface (not implemented).
179    C         in the lower layers (e.g. at k=1).
180    C
181    c         ddRm1=atm_cp*( ((rF( K )/atm_po)**atm_kappa)
182    c    &                  -((rC(K-1)/atm_po)**atm_kappa) )
183    c         ddRp1=atm_cp*( ((rC( K )/atm_po)**atm_kappa)
184    c    &                  -((rF( K )/atm_po)**atm_kappa) )
185    C-----------------------------------------------------------------------
186    
187    
188    C-------- This discretization is the energy conserving form
189              ddRp1=atm_cp*( ((rC( K )/atm_po)**atm_kappa)
190         &                  -((rC(K-1)/atm_po)**atm_kappa) )*0.5
191              ddRm1=ddRp1
192    C-----------------------------------------------------------------------
193    
194              DO j=jMin,jMax
195                DO i=iMin,iMax
196                  ddRp=ddRp1
197                  ddRm=ddRm1
198                  IF (hFacC(I,J, K ,bi,bj).EQ.0.) ddRp=0.
199                  IF (hFacC(I,J,K-1,bi,bj).EQ.0.) ddRm=0.
200                  phiHyd(i,j,K)=phiHyd(i,j,K-1)
201         &           -( ddRm*(theta(I,J,K-1,bi,bj)-tRef(K-1))
202         &             +ddRp*(theta(I,J, K ,bi,bj)-tRef( K )) )
203    C             Old code (atmos-exact) looked like this
204    Cold          phiHyd(i,j,K)=phiHyd(i,j,K-1) - ddRm1*
205    Cold &      (theta(I,J,K-1,bi,bj)+theta(I,J,K,bi,bj)-2.*tRef(K))
206                ENDDO
207              ENDDO
208            ENDIF
209    
210    
211          ELSE
212            STOP 'CALC_PHI_HYD: We should never reach this point!'
213          ENDIF
214    
215  #endif  #endif
216    
217  ! --------------------------------------------------------------------        RETURN
218        return        END
       end  
 ! ====================================================================  

Legend:
Removed from v.1.7  
changed lines
  Added in v.1.13

  ViewVC Help
Powered by ViewVC 1.1.22