/[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.8.2.1 by adcroft, Fri Jan 12 21:02:46 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, phiHydInterface,
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     |   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     \==========================================================/  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        _RL phiHydInterface(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
44  C     == Local variables ==        INTEGER myThid
       INTEGER i,j,Km1  
       _RL halfLayer  
       _RL gamma  
45    
46  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE  #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
47    
48        if (K.eq.1) then  C     == Local variables ==
49         Km1=1        INTEGER i,j
50         halfLayer=0.5 _d 0        _RL alphaRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51        else        _RL dRloc,dRlocKp1
52         Km1=K-1  
53         halfLayer=1.0 _d 0        IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
54        endif  
55            dRloc=drC(k)
56  C--   Scale factor for hydrostatic relation except for ocean in          IF (k.EQ.1) dRloc=drF(1)
57  C--   pressure coords.          IF (k.EQ.Nr) THEN
58        gamma = 1. _d 0            dRlocKp1=0.
59  C--   Scale factor for hydrostatic relation for ocean in pressure          ELSE
60  C--   coords.            dRlocKp1=drC(k+1)
61        IF ( buoyancyRelation .EQ. 'OCEANIC' .AND. usingPCoords ) THEN          ENDIF
62         gamma = recip_Gravity*recip_rhoConst  
63        ENDIF  C--     If this is the top layer we impose the boundary condition
64    C       P(z=eta) = P(atmospheric_loading)
65  C--   Contribution to phiHyd(:,:,K) from buoy(:,:,K-1) + buoy(:,:,K)          IF (k.EQ.1) THEN
66  C     (This is now the actual hydrostatic pressure|height at the T/S            DO j=jMin,jMax
67  C     points)              DO i=iMin,iMax
68        DO j=jMin,jMax  C             *NOTE* The loading should go here but has not been implemented yet
69         DO i=iMin,iMax                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  #ifdef ALLOW_AUTODIFF_TAMC
84              Is this directive correct or even necessary in this new code?
85  CADJ GENERAL  CADJ GENERAL
86  #endif  #endif
87          phiHyd(i,j,K)=phiHyd(i,j,Km1)-rhoConst*halfLayer  C           This discretization is the "finite volume" form
88       &  *0.5 _d 0*( drF(Km1)+drF(K) )*gamma  C           which has not been used to date since it does not
89       &  *0.5 _d 0*( buoyKM1(i,j)+buoyKP1(i,j) )  C           conserve KE+PE exactly even though it is more natural
90         ENDDO  C
91        ENDDO  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  #endif
119    

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

  ViewVC Help
Powered by ViewVC 1.1.22