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

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

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


Revision 1.7 - (show annotations) (download)
Fri May 2 16:57:43 2014 UTC (10 years ago) by jmc
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65b, checkpoint65c, checkpoint65a, checkpoint65f, checkpoint65g, checkpoint65d, checkpoint65e, checkpoint65, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, checkpoint64y, checkpoint64x, checkpoint64z, checkpoint64w, HEAD
Changes since 1.6: +2 -2 lines
use pStarFacK (now stored in commom block) instead of re-computing it

1 C $Header: /u/gcmpack/MITgcm/model/src/diags_phi_hyd.F,v 1.6 2013/08/14 15:46:01 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: DIAGS_PHI_HYD
9 C !INTERFACE:
10 SUBROUTINE DIAGS_PHI_HYD(
11 I k, bi, bj, iMin,iMax, jMin,jMax,
12 I phiHydC,
13 I myTime, myIter, myThid)
14 C !DESCRIPTION: \bv
15 C *==========================================================*
16 C | S/R DIAGS_PHI_HYD
17 C | o Diagnose full hydrostatic Potential at cell center ;
18 C | used for output & with EOS funct. of P
19 C *==========================================================*
20 C | NOTE: For now, only contains the (total) Potential anomaly
21 C | since phiRef (for Atmos) is not available (not in common)
22 C *==========================================================*
23 C \ev
24
25 C !USES:
26 IMPLICIT NONE
27 C == Global variables ==
28 #include "SIZE.h"
29 #include "EEPARAMS.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32 #include "SURFACE.h"
33 #include "DYNVARS.h"
34
35 C !INPUT/OUTPUT PARAMETERS:
36 C == Routine Arguments ==
37 C k, bi,bj :: level & tile indices
38 C iMin,iMax,jMin,jMax :: Loop counters
39 C phiHydC :: hydrostatic potential anomaly at cell center
40 C (atmos: =Geopotential ; ocean-z: =Pressure/rho)
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 _RL phiHydC(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
46 _RL myTime
47 INTEGER myIter, myThid
48
49 #ifdef INCLUDE_PHIHYD_CALCULATION_CODE
50
51 C !LOCAL VARIABLES:
52 C == Local variables ==
53 C i,j :: Loop counters
54 C phiHydCstR :: total hydrostatic Potential (anomaly, for now),
55 C at fixed r-position, cell center level location.
56 INTEGER i,j
57 #ifdef NONLIN_FRSURF
58 _RL facP, dPhiRef
59 _RL phiHydCstR(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
60 #endif /* NONLIN_FRSURF */
61 CEOP
62
63 DO j=jMin,jMax
64 DO i=iMin,iMax
65 totPhiHyd(i,j,k,bi,bj) = phiHydC(i,j)
66 & + Bo_surf(i,j,bi,bj)*etaN(i,j,bi,bj)
67 & + phi0surf(i,j,bi,bj)
68 #ifdef NONLIN_FRSURF
69 phiHydCstR(i,j) = totPhiHyd(i,j,k,bi,bj)
70 #endif /* NONLIN_FRSURF */
71 ENDDO
72 ENDDO
73
74 #ifdef NONLIN_FRSURF
75 c IF (select_rStar.GE.2 .AND. nonlinFreeSurf.GE.4 ) THEN
76 IF (select_rStar.GE.1 .AND. nonlinFreeSurf.GE.4 ) THEN
77 c# ifndef DISABLE_RSTAR_CODE
78 C- Integral of b.dr = rStarFac * Integral of b.dr* :
79 IF ( fluidIsAir ) THEN
80 C- Consistent with Phi'= Integr[ theta'.dPi ] :
81 DO j=jMin,jMax
82 DO i=iMin,iMax
83 facP = pStarFacK(i,j,bi,bj)
84 dPhiRef = phiRef(2*k) - gravity*topoZ(i,j,bi,bj)
85 & - phi0surf(i,j,bi,bj)
86 totPhiHyd(i,j,k,bi,bj) =
87 & phiHydC(i,j)*facP
88 & + MAX( dPhiRef, 0. _d 0 )*( facP - 1. _d 0 )
89 & + phi0surf(i,j,bi,bj)
90 c phiHydCstR(i,j) = phiHydCstR(i,j)
91 c & + phiHydC(i,j)*( facP - 1. _d 0 )
92 ENDDO
93 ENDDO
94 ELSEIF ( usingPCoords ) THEN
95 DO j=jMin,jMax
96 DO i=iMin,iMax
97 c & dPhiRef = phiRef(2*k) - gravity*topoZ(i,j,bi,bj)
98 c & - phi0surf(i,j,bi,bj)
99 C-- assume PhiRef is just (ps0 - p)/rhoConst :
100 dPhiRef =( Ro_surf(i,j,bi,bj)-rC(k) )*recip_rhoConst
101 totPhiHyd(i,j,k,bi,bj) =
102 & phiHydC(i,j)*rStarFacC(i,j,bi,bj)
103 & + MAX( dPhiRef, 0. _d 0 )
104 & *( rStarFacC(i,j,bi,bj) - 1. _d 0 )
105 & + phi0surf(i,j,bi,bj)
106 c totPhiHyd(i,j,k,bi,bj) = phiHydCstR(i,j)
107 ENDDO
108 ENDDO
109 ELSE
110 DO j=jMin,jMax
111 DO i=iMin,iMax
112 dPhiRef =( Ro_surf(i,j,bi,bj)-rC(k) )*gravity
113 totPhiHyd(i,j,k,bi,bj) =
114 & phiHydC(i,j)*rStarFacC(i,j,bi,bj)
115 & + MAX( dPhiRef, 0. _d 0 )
116 & *( rStarFacC(i,j,bi,bj) - 1. _d 0 )
117 & + phi0surf(i,j,bi,bj)
118 c totPhiHyd(i,j,k,bi,bj) = phiHydCstR(i,j)
119 ENDDO
120 ENDDO
121 ENDIF
122 #ifdef ALLOW_DIAGNOSTICS
123 C-- skip diagnostics if called from INI_PRESSURE
124 IF ( useDiagnostics .AND. myIter.GE.0 ) THEN
125 CALL DIAGNOSTICS_FILL(phiHydCstR,'PHIHYDcR',k,1,2,bi,bj,myThid)
126 ENDIF
127 #endif /* ALLOW_DIAGNOSTICS */
128
129 c# endif /* DISABLE_RSTAR_CODE */
130 ENDIF
131 #endif /* NONLIN_FRSURF */
132
133 #endif /* INCLUDE_PHIHYD_CALCULATION_CODE */
134
135 RETURN
136 END

  ViewVC Help
Powered by ViewVC 1.1.22