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

Contents of /MITgcm/model/src/diags_phi_rlow.F

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


Revision 1.1 - (show annotations) (download)
Sun Feb 9 02:58:39 2003 UTC (21 years, 4 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint48e_post, checkpoint48f_post
o New S/R for diagnostic of bottom pressure
  (phi0surf contribution was missing in checkpoint48d_post)

1 C $Header: $
2 C $Name: $
3
4 #include "CPP_OPTIONS.h"
5
6 CBOP
7 C !ROUTINE: DIAGS_PHI_RLOW
8 C !INTERFACE:
9 SUBROUTINE DIAGS_PHI_RLOW(
10 I k, bi, bj, iMin,iMax, jMin,jMax,
11 I phiHyd, alphRho, tFld, sFld,
12 I myTime, myIter, myThid)
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | S/R DIAGS_PHI_RLOW
16 C | o Diagnose Phi-Hydrostatic at r-lower boundary
17 C | = bottom pressure (ocean in z-coord) ;
18 C | = sea surface elevation (ocean in p-coord) ;
19 C | = height at the top of atmosphere (in p-coord) ;
20 C *==========================================================*
21 C \ev
22
23 C !USES:
24 IMPLICIT NONE
25 C == Global variables ==
26 #include "SIZE.h"
27 #include "EEPARAMS.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31 #include "DYNVARS.h"
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C == Routine Arguments ==
35 C bi,bj :: tile index
36 C iMin,iMax,jMin,jMax :: Loop counters
37 C phiHyd :: Hydrostatic Potential anomaly
38 C (atmos: =Geopotential ; ocean-z: =Pressure/rho)
39 C alphRho :: Density (z-coord) or specific volume (p-coord)
40 C tFld :: Potential temp.
41 C sFld :: Salinity
42 C myTime :: Current time
43 C myIter :: Current iteration number
44 C myThid :: Instance number for this call of the routine.
45 INTEGER k, bi,bj, iMin,iMax, jMin,jMax
46 _RL phiHyd(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr)
47 _RL alphRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
48 _RL tFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
49 _RL sFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
50 _RL myTime
51 INTEGER myIter, myThid
52
53 #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
54
55 C !LOCAL VARIABLES:
56 C == Local variables ==
57 C i,j :: Loop counters
58 INTEGER i,j
59 _RL zero, one, half
60 _RL dRloc
61 PARAMETER ( zero= 0. _d 0 , one= 1. _d 0 , half= .5 _d 0 )
62 CEOP
63
64 dRloc=drC(k)
65 IF (k.EQ.1) dRloc=drF(1)
66
67 IF ( buoyancyRelation .eq. 'OCEANIC' ) THEN
68
69 IF (integr_GeoPot.EQ.1) THEN
70 C -- Finite Volume Form
71
72 DO j=jMin,jMax
73 DO i=iMin,iMax
74 IF ( k .EQ. kLowC(i,j,bi,bj) ) THEN
75 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
76 & + hFacC(i,j,k,bi,bj)
77 & *drF(K)*gravity*alphRho(i,j)*recip_rhoConst
78 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
79 & + phi0surf(i,j,bi,bj)
80 ENDIF
81 ENDDO
82 ENDDO
83
84 ELSE
85 C -- Finite Difference Form
86
87 C---------- Compute bottom pressure deviation from gravity*rho0*H
88 C This has to be done starting from phiHyd at the current
89 C tracer point and .5 of the cell's thickness has to be
90 C substracted from hFacC
91
92 DO j=jMin,jMax
93 DO i=iMin,iMax
94 IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
95 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
96 & + (half*dRloc+(hFacC(i,j,k,bi,bj)-half)*drF(k))
97 & *gravity*alphRho(i,j)*recip_rhoConst
98 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
99 & + phi0surf(i,j,bi,bj)
100 ENDIF
101 ENDDO
102 ENDDO
103
104 C -- end if integr_GeoPot = ...
105 ENDIF
106
107 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
108 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
109
110 IF (integr_GeoPot.EQ.1) THEN
111 C -- Finite Volume Form
112
113 DO j=jMin,jMax
114 DO i=iMin,iMax
115 IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
116 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
117 & + hFacC(i,j,k,bi,bj)*drF(K)*alphRho(i,j)
118 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
119 & + phi0surf(i,j,bi,bj)
120 ENDIF
121 ENDDO
122 ENDDO
123
124 ELSE
125 C -- Finite Difference Form
126
127 C---------- Compute gravity*(sea surface elevation) first
128 C This has to be done starting from phiHyd at the current
129 C tracer point and .5 of the cell's thickness has to be
130 C substracted from hFacC
131
132 DO j=jMin,jMax
133 DO i=iMin,iMax
134 IF ( K .EQ. kLowC(i,j,bi,bj) ) THEN
135 phiHydLow(i,j,bi,bj) = phiHyd(i,j,k)
136 & + ( half*dRloc+(hFacC(i,j,k,bi,bj)-half)*drF(k)
137 & )*alphRho(i,j)
138 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
139 & + phi0surf(i,j,bi,bj)
140 ENDIF
141 ENDDO
142 ENDDO
143
144 C -- end if integr_GeoPot = ...
145 ENDIF
146
147 c ELSEIF ( buoyancyRelation .eq. 'ATMOSPHERIC' ) THEN
148 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
149 ENDIF
150
151 #endif /* INCLUDE_PHIHYD_CALCULATION_CODE */
152
153 RETURN
154 END

  ViewVC Help
Powered by ViewVC 1.1.22