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

Annotation of /MITgcm/model/src/calc_grad_phi_hyd.F

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


Revision 1.14 - (hide annotations) (download)
Wed Dec 14 01:12:59 2011 UTC (12 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63g, checkpoint64, checkpoint63p, checkpoint63q, checkpoint63r, checkpoint63s, checkpoint63l, checkpoint63m, checkpoint63n, checkpoint63o, checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63k, checkpoint64a, checkpoint64b
Changes since 1.13: +12 -4 lines
apply mask to output (horiz. gradient of Hydrostatic potential):
 - does not contaminate gUnm1,gVnm1 in pickup files
 - also get nicer diagnostics 'Um_dPHdx' & 'Vm_dPHdy'

1 jmc 1.14 C $Header: /u/gcmpack/MITgcm/model/src/calc_grad_phi_hyd.F,v 1.13 2010/09/10 17:23:17 jmc Exp $
2 jmc 1.1 C $Name: $
3    
4     #include "CPP_OPTIONS.h"
5    
6     CBOP
7     C !ROUTINE: CALC_GRAD_PHI_HYD
8     C !INTERFACE:
9 jmc 1.9 SUBROUTINE CALC_GRAD_PHI_HYD(
10 jmc 1.1 I k, bi, bj, iMin,iMax, jMin,jMax,
11 jmc 1.3 I phiHydC, alphRho, tFld, sFld,
12 jmc 1.1 O dPhiHydX, dPhiHydY,
13     I myTime, myIter, myThid)
14     C !DESCRIPTION: \bv
15     C *==========================================================*
16 jmc 1.9 C | S/R CALC_GRAD_PHI_HYD
17     C | o Calculate the gradient of Hydrostatic potential anomaly
18 jmc 1.1 C *==========================================================*
19     C \ev
20    
21     C !USES:
22     IMPLICIT NONE
23     C == Global variables ==
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "GRID.h"
28     #include "SURFACE.h"
29 jmc 1.3 #include "DYNVARS.h"
30 jmc 1.1
31     C !INPUT/OUTPUT PARAMETERS:
32     C == Routine Arguments ==
33 jmc 1.9 C bi,bj :: tile index
34 jmc 1.1 C iMin,iMax,jMin,jMax :: Loop counters
35 jmc 1.9 C phiHydC :: Hydrostatic Potential anomaly
36 jmc 1.1 C (atmos: =Geopotential ; ocean-z: =Pressure/rho)
37     C alphRho :: Density (z-coord) or specific volume (p-coord)
38     C tFld :: Potential temp.
39 jmc 1.9 C sFld :: Salinity
40 jmc 1.1 C dPhiHydX,Y :: Gradient (X & Y directions) of Hyd. Potential
41     C myTime :: Current time
42     C myIter :: Current iteration number
43     C myThid :: Instance number for this call of the routine.
44     INTEGER k, bi,bj, iMin,iMax, jMin,jMax
45 jmc 1.3 _RL phiHydC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46 jmc 1.1 _RL alphRho(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
47     _RL tFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
48     _RL sFld(1-OLx:sNx+OLx,1-OLy:sNy+OLy,Nr,nSx,nSy)
49 jmc 1.14 _RL dPhiHydX(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
50     _RL dPhiHydY(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
51 jmc 1.1 _RL myTime
52     INTEGER myIter, myThid
53    
54     #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
55    
56     C !LOCAL VARIABLES:
57     C == Local variables ==
58     C i,j :: Loop counters
59     INTEGER i,j
60 jmc 1.14 _RL varLoc(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
61 jmc 1.7 #ifdef NONLIN_FRSURF
62 jmc 1.3 _RL factorZ, factorP, conv_theta2T
63 jmc 1.5 _RL factPI
64     CHARACTER*(MAX_LEN_MBUF) msgBuf
65 jmc 1.7 #endif
66 jmc 1.1 CEOP
67    
68 jmc 1.3 #ifdef NONLIN_FRSURF
69 jmc 1.5 IF (select_rStar.GE.2 .AND. nonlinFreeSurf.GE.4 ) THEN
70 heimbach 1.8 # ifndef DISABLE_RSTAR_CODE
71 jmc 1.5 C- Integral of b.dr = rStarFac * Integral of b.dr* :
72 jmc 1.9 C and will add later (select_rStar=2) the contribution of
73 jmc 1.5 C the slope of the r* coordinate.
74     IF ( buoyancyRelation .EQ. 'ATMOSPHERIC' ) THEN
75     C- Consistent with Phi'= Integr[ theta'.dPi ] :
76 jmc 1.10 DO j=jMin,jMax
77     DO i=iMin,iMax
78 jmc 1.5 varLoc(i,j) = phiHydC(i,j)*rStarFacC(i,j,bi,bj)**atm_kappa
79     & + phi0surf(i,j,bi,bj)
80     ENDDO
81     ENDDO
82     ELSE
83 jmc 1.10 DO j=jMin,jMax
84     DO i=iMin,iMax
85 jmc 1.5 varLoc(i,j) = phiHydC(i,j)*rStarFacC(i,j,bi,bj)
86     & + phi0surf(i,j,bi,bj)
87     ENDDO
88     ENDDO
89     ENDIF
90     ELSEIF (select_rStar.GE.1 .AND. nonlinFreeSurf.GE.4 ) THEN
91     C- Integral of b.dr but scaled to correspond to a fixed r-level (=r*)
92     C no contribution of the slope of the r* coordinate (select_rStar=1)
93     IF ( buoyancyRelation .EQ. 'ATMOSPHERIC' ) THEN
94     C- Consistent with Phi'= Integr[ theta'.dPi ] :
95 jmc 1.10 DO j=jMin,jMax
96     DO i=iMin,iMax
97 jmc 1.5 IF (Ro_surf(i,j,bi,bj).EQ.rC(k)) THEN
98 jmc 1.9 factPI=atm_Cp*( ((etaH(i,j,bi,bj)+rC(k))/atm_Po)**atm_kappa
99     & -( rC(k) /atm_Po)**atm_kappa
100 jmc 1.5 & )
101     varLoc(i,j) = factPI*alphRho(i,j)
102 jmc 1.13 & + phi0surf(i,j,bi,bj)
103 jmc 1.5 ELSEIF (Ro_surf(i,j,bi,bj).NE.0. _d 0) THEN
104     factPI = (rC(k)/Ro_surf(i,j,bi,bj))**atm_kappa
105     varLoc(i,j) = phiHydC(i,j)
106     & *(rStarFacC(i,j,bi,bj)**atm_kappa - factPI)
107     & /(1. _d 0 -factPI)
108     & + phi0surf(i,j,bi,bj)
109     ENDIF
110     ENDDO
111     ENDDO
112     ELSE
113 jmc 1.10 DO j=jMin,jMax
114     DO i=iMin,iMax
115 jmc 1.5 IF (Ro_surf(i,j,bi,bj).EQ.rC(k)) THEN
116 jmc 1.6 WRITE(msgBuf,'(3A)') 'CALC_GRAD_PHI_HYD: ',
117     & 'Problem when Ro_surf=rC',
118     & ' with select_rStar,integr_GeoPot=1,4'
119 jmc 1.5 CALL PRINT_ERROR( msgBuf , myThid)
120     STOP 'CALC_GRAD_PHI_HYD: Pb in r* options implementation'
121     ELSE
122     varLoc(i,j) = phiHydC(i,j)
123     & *(etaH(i,j,bi,bj)+Ro_surf(i,j,bi,bj)-rC(k))
124     & / (Ro_surf(i,j,bi,bj)-rC(k))
125     & + phi0surf(i,j,bi,bj)
126     ENDIF
127     ENDDO
128 jmc 1.3 ENDDO
129 jmc 1.5 ENDIF
130 heimbach 1.8 # endif /* DISABLE_RSTAR_CODE */
131 jmc 1.3 ELSE
132     #else /* NONLIN_FRSURF */
133     IF (.TRUE.) THEN
134     #endif /* NONLIN_FRSURF */
135 jmc 1.10 DO j=jMin,jMax
136     DO i=iMin,iMax
137 jmc 1.3 varLoc(i,j) = phiHydC(i,j)+phi0surf(i,j,bi,bj)
138     ENDDO
139     ENDDO
140     ENDIF
141 jmc 1.1
142 jmc 1.3 C-- Zonal & Meridional gradient of potential anomaly
143 jmc 1.12 DO j=1-OLy,sNy+OLy
144     DO i=1-OLx,sNx+OLx
145     dPhiHydX(i,j) = 0. _d 0
146     dPhiHydY(i,j) = 0. _d 0
147     ENDDO
148     ENDDO
149 jmc 1.1 DO j=jMin,jMax
150 jmc 1.10 DO i=iMin+1,iMax
151 jmc 1.9 dPhiHydX(i,j) = _recip_dxC(i,j,bi,bj)*recip_deepFacC(k)
152     & *( varLoc(i,j)-varLoc(i-1,j) )*recip_rhoFacC(k)
153 jmc 1.10 ENDDO
154     ENDDO
155     DO j=jMin+1,jMax
156     DO i=iMin,iMax
157 jmc 1.9 dPhiHydY(i,j) = _recip_dyC(i,j,bi,bj)*recip_deepFacC(k)
158     & *( varLoc(i,j)-varLoc(i,j-1) )*recip_rhoFacC(k)
159 jmc 1.1 ENDDO
160     ENDDO
161 jmc 1.3
162     #ifdef NONLIN_FRSURF
163     IF (select_rStar.GE.2 .AND. nonlinFreeSurf.GE.1 ) THEN
164     IF ( buoyancyRelation .EQ. 'OCEANIC' ) THEN
165 jmc 1.11 C-- z* coordinate slope term: rho_prime/rho0 * Grad_r(g.z)
166 jmc 1.9 factorZ = gravity*recip_rhoConst*recip_rhoFacC(k)*0.5 _d 0
167 jmc 1.10 DO j=jMin,jMax
168     DO i=iMin,iMax
169 jmc 1.3 varLoc(i,j) = etaH(i,j,bi,bj)
170     & *(1. _d 0 + rC(k)*recip_Rcol(i,j,bi,bj))
171     ENDDO
172     ENDDO
173     DO j=jMin,jMax
174 jmc 1.10 DO i=iMin+1,iMax
175 jmc 1.3 dPhiHydX(i,j) = dPhiHydX(i,j)
176     & +factorZ*(alphRho(i-1,j)+alphRho(i,j))
177     & *(varLoc(i,j)-varLoc(i-1,j))
178 jmc 1.9 & *recip_dxC(i,j,bi,bj)*recip_deepFacC(k)
179 jmc 1.10 ENDDO
180     ENDDO
181     DO j=jMin+1,jMax
182     DO i=iMin,iMax
183 jmc 1.3 dPhiHydY(i,j) = dPhiHydY(i,j)
184     & +factorZ*(alphRho(i,j-1)+alphRho(i,j))
185     & *(varLoc(i,j)-varLoc(i,j-1))
186 jmc 1.9 & *recip_dyC(i,j,bi,bj)*recip_deepFacC(k)
187 jmc 1.3 ENDDO
188     ENDDO
189     ELSEIF (buoyancyRelation .EQ. 'OCEANICP' ) THEN
190 jmc 1.11 C-- p* coordinate slope term: alpha_prime * Grad_r( p )
191 jmc 1.3 factorP = 0.5 _d 0
192     DO j=jMin,jMax
193 jmc 1.10 DO i=iMin+1,iMax
194 jmc 1.3 dPhiHydX(i,j) = dPhiHydX(i,j)
195     & +factorP*(alphRho(i-1,j)+alphRho(i,j))
196     & *(rStarFacC(i,j,bi,bj)-rStarFacC(i-1,j,bi,bj))
197 jmc 1.9 & *rC(k)*recip_dxC(i,j,bi,bj)*recip_deepFacC(k)
198 jmc 1.10 ENDDO
199     ENDDO
200     DO j=jMin+1,jMax
201     DO i=iMin,iMax
202 jmc 1.3 dPhiHydY(i,j) = dPhiHydY(i,j)
203     & +factorP*(alphRho(i,j-1)+alphRho(i,j))
204     & *(rStarFacC(i,j,bi,bj)-rStarFacC(i,j-1,bi,bj))
205 jmc 1.9 & *rC(k)*recip_dyC(i,j,bi,bj)*recip_deepFacC(k)
206 jmc 1.3 ENDDO
207     ENDDO
208     ELSEIF ( buoyancyRelation .EQ. 'ATMOSPHERIC' ) THEN
209 jmc 1.11 C-- p* coordinate slope term: alpha_prime * Grad_r( p )
210 jmc 1.3 conv_theta2T = (rC(k)/atm_Po)**atm_kappa
211     factorP = (atm_Rd/rC(k))*conv_theta2T*0.5 _d 0
212     DO j=jMin,jMax
213 jmc 1.10 DO i=iMin+1,iMax
214 jmc 1.3 dPhiHydX(i,j) = dPhiHydX(i,j)
215 jmc 1.5 & +factorP*(alphRho(i-1,j)+alphRho(i,j))
216 jmc 1.3 & *(rStarFacC(i,j,bi,bj)-rStarFacC(i-1,j,bi,bj))
217 jmc 1.9 & *rC(k)*recip_dxC(i,j,bi,bj)*recip_deepFacC(k)
218 jmc 1.10 ENDDO
219     ENDDO
220     DO j=jMin+1,jMax
221     DO i=iMin,iMax
222 jmc 1.3 dPhiHydY(i,j) = dPhiHydY(i,j)
223 jmc 1.5 & +factorP*(alphRho(i,j-1)+alphRho(i,j))
224 jmc 1.3 & *(rStarFacC(i,j,bi,bj)-rStarFacC(i,j-1,bi,bj))
225 jmc 1.9 & *rC(k)*recip_dyC(i,j,bi,bj)*recip_deepFacC(k)
226 jmc 1.3 ENDDO
227     ENDDO
228     ENDIF
229     ENDIF
230     #endif /* NONLIN_FRSURF */
231 jmc 1.1
232 jmc 1.14 C-- Apply mask:
233     DO j=1-OLy,sNy+OLy
234     DO i=1-OLx,sNx+OLx
235     dPhiHydX(i,j) = dPhiHydX(i,j)*_maskW(i,j,k,bi,bj)
236     dPhiHydY(i,j) = dPhiHydY(i,j)*_maskS(i,j,k,bi,bj)
237     ENDDO
238     ENDDO
239    
240 jmc 1.1 #endif /* INCLUDE_PHIHYD_CALCULATION_CODE */
241    
242     RETURN
243     END

  ViewVC Help
Powered by ViewVC 1.1.22