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

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

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


Revision 1.24 - (show annotations) (download)
Mon May 12 01:27:47 2014 UTC (9 years, 11 months 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, HEAD
Changes since 1.23: +65 -43 lines
- With p* or Sigma-P, use constant reference Pot.Temp (thetaConst) instead
  of vertical profile tRef in geopotential background and anomaly.

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_linear_phisurf.F,v 1.23 2013/11/22 01:07:11 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: INI_LINEAR_PHISURF
9 C !INTERFACE:
10 SUBROUTINE INI_LINEAR_PHISURF( myThid )
11
12 C !DESCRIPTION: \bv
13 C *==========================================================*
14 C | SUBROUTINE INI_LINEAR_PHISURF
15 C | o Initialise the Linear Relation Phi_surf(eta)
16 C *==========================================================*
17 C | Initialise -Buoyancy at surface level (Bo_surf)
18 C | to setup the Linear relation: Phi_surf(eta)=Bo_surf*eta
19 C | Initialise phi0surf = starting point for integrating
20 C | phiHyd (= phiHyd at r=RoSurf)
21 C *==========================================================*
22 C \ev
23
24 C !USES:
25 IMPLICIT NONE
26 C === Global variables ===
27 #include "SIZE.h"
28 #include "EEPARAMS.h"
29 #include "PARAMS.h"
30 #include "GRID.h"
31 #include "SURFACE.h"
32
33 C !INPUT/OUTPUT PARAMETERS:
34 C === Routine arguments ===
35 C myThid :: my Thread Id number
36 INTEGER myThid
37
38 C == Local variables in common ==
39 C topoHloc had to be in common for multi threading but no longer
40 C needed since MDSIO now allows (2009/06/07) to write local arrays
41
42 C !LOCAL VARIABLES:
43 C === Local variables ===
44 C topoHloc :: Temporary array used to write surface topography
45 C bi,bj :: tile indices
46 C i,j,k :: Loop counters
47 _RS topoHloc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
48 INTEGER bi, bj
49 INTEGER i, j, k
50 _RL pLoc, rhoLoc
51 _RL dPIdp
52 CEOP
53
54 C-- Initialisation
55 #ifdef ALLOW_AUTODIFF
56 DO bj=myByLo(myThid),myByHi(myThid)
57 DO bi=myBxLo(myThid),myBxHi(myThid)
58 DO j=1-OLy,sNy+OLy
59 DO i=1-OLx,sNx+OLx
60 Bo_surf(i,j,bi,bj) = 0. _d 0
61 recip_Bo(i,j,bi,bj) = 0. _d 0
62 ENDDO
63 ENDDO
64 ENDDO
65 ENDDO
66 #endif /* ALLOW_AUTODIFF */
67
68 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
69
70 C-- Initialise -Buoyancy at surface level : Bo_surf
71 C Bo_surf is defined as d/dr(Phi_surf) and set to g/z2rUnit with
72 C z2rUnit = conversion factor from z-unit to r-unit: [z] * z2rUnit = [r]
73 C an accurate formulation includes P_surf and T,S_ref effects on rho_surf:
74 C (setting uniformLin_PhiSurf=.FALSE.):
75 C z-coord (z2rUnit=1): Bo_surf = - Buoyancy
76 C = g * rho_surf(Tref,Sref,pSurf_0)/rho_0
77 C p-coord (z2rUnit=rho*g): Bo_surf = 1/rho(Tref(ksurf),pSurf_0)
78 C Note: on Phi_surf splitting : Non-linear Time-dependent effects on B_surf
79 C [through eta & (T-tRef)_surf] are included in PhiHyd rather than in Bo_surf
80 C--
81 IF ( usingZCoords ) THEN
82 C- gBaro = gravity (except for External mode test with reduced gravity)
83 DO bj=myByLo(myThid),myByHi(myThid)
84 DO bi=myBxLo(myThid),myBxHi(myThid)
85 DO j=1-OLy,sNy+OLy
86 DO i=1-OLx,sNx+OLx
87 Bo_surf(i,j,bi,bj) = gBaro
88 recip_Bo(i,j,bi,bj) = 1. _d 0 / gBaro
89 ENDDO
90 ENDDO
91 ENDDO
92 ENDDO
93 ELSEIF ( uniformLin_PhiSurf ) THEN
94 C- use a linear (in ps) uniform relation : Phi'_surf = 1/rhoConst * ps'_surf
95 DO bj=myByLo(myThid),myByHi(myThid)
96 DO bi=myBxLo(myThid),myBxHi(myThid)
97 DO j=1-OLy,sNy+OLy
98 DO i=1-OLx,sNx+OLx
99 c Bo_surf(i,j,bi,bj) = rVel2wUnit(1)*gravity
100 c recip_Bo(i,j,bi,bj) = wUnit2rVel(1)*recip_gravity
101 Bo_surf(i,j,bi,bj) = recip_rhoConst
102 recip_Bo(i,j,bi,bj) = rhoConst
103 ENDDO
104 ENDDO
105 ENDDO
106 ENDDO
107 ELSEIF ( fluidIsWater ) THEN
108 C-- More precise than uniformLin_PhiSurf case but inconsistent
109 C with nonlinFreeSurf=4 in CALC_PHI_HYD (eta contribution to phiHyd)
110 DO bj=myByLo(myThid),myByHi(myThid)
111 DO bi=myBxLo(myThid),myBxHi(myThid)
112 DO j=1-OLy,sNy+OLy
113 DO i=1-OLx,sNx+OLx
114 IF ( Ro_surf(i,j,bi,bj).GT.0. _d 0
115 & .AND. kSurfC(i,j,bi,bj).LE.Nr ) THEN
116 pLoc = Ro_surf(i,j,bi,bj)
117 #ifdef ALLOW_OPENAD
118 CALL FIND_RHO_SCALAR(
119 I tRef(kSurfC(i,j,bi,bj)),
120 I sRef(kSurfC(i,j,bi,bj)),
121 I pLoc,
122 O rhoLoc, myThid )
123 #else /* ALLOW_OPENAD */
124 k = kSurfC(i,j,bi,bj)
125 CALL FIND_RHO_SCALAR(
126 I tRef(k), sRef(k), pLoc,
127 O rhoLoc, myThid )
128 #endif /* ALLOW_OPENAD */
129 IF ( rhoLoc .EQ. 0. _d 0 ) THEN
130 Bo_surf(i,j,bi,bj) = 0. _d 0
131 ELSE
132 Bo_surf(i,j,bi,bj) = 1. _d 0/rhoLoc
133 ENDIF
134 recip_Bo(i,j,bi,bj) = rhoLoc
135 ELSE
136 Bo_surf(i,j,bi,bj) = 0. _d 0
137 recip_Bo(i,j,bi,bj) = 0. _d 0
138 ENDIF
139 ENDDO
140 ENDDO
141 ENDDO
142 ENDDO
143 ELSEIF ( fluidIsAir ) THEN
144 C- use a linearized (in ps) Non-uniform relation : Bo_surf(Po_surf,tRef_surf)
145 C Bo = d/d_p(Phi_surf) = tRef_surf*d/d_p(PI) ; PI = Cp*(p/Po)^kappa
146 C and atm_Cp*atm_kappa = atm_Rd
147 DO bj=myByLo(myThid),myByHi(myThid)
148 DO bi=myBxLo(myThid),myBxHi(myThid)
149 IF ( select_rStar.GE.1 .OR. selectSigmaCoord.GE.1 ) THEN
150 C- isothermal (theta=const) reference state
151 DO j=1-OLy,sNy+OLy
152 DO i=1-OLx,sNx+OLx
153 IF ( Ro_surf(i,j,bi,bj).GT.0. _d 0
154 & .AND. kSurfC(i,j,bi,bj).LE.Nr ) THEN
155 dPIdp = (atm_Rd/atm_Po)*
156 & (Ro_surf(i,j,bi,bj)/atm_Po)**(atm_kappa-1. _d 0)
157 Bo_surf(i,j,bi,bj) = dPIdp*thetaConst
158 recip_Bo(i,j,bi,bj) = 1. _d 0 / Bo_surf(i,j,bi,bj)
159 ELSE
160 Bo_surf(i,j,bi,bj) = 0.
161 recip_Bo(i,j,bi,bj) = 0.
162 ENDIF
163 ENDDO
164 ENDDO
165 ELSE
166 C- horizontally uniform (tRef) reference state
167 DO j=1-OLy,sNy+OLy
168 DO i=1-OLx,sNx+OLx
169 IF ( Ro_surf(i,j,bi,bj).GT.0. _d 0
170 & .AND. kSurfC(i,j,bi,bj).LE.Nr ) THEN
171 dPIdp = (atm_Rd/atm_Po)*
172 & (Ro_surf(i,j,bi,bj)/atm_Po)**(atm_kappa-1. _d 0)
173 Bo_surf(i,j,bi,bj) = dPIdp*tRef(kSurfC(i,j,bi,bj))
174 recip_Bo(i,j,bi,bj) = 1. _d 0 / Bo_surf(i,j,bi,bj)
175 ELSE
176 Bo_surf(i,j,bi,bj) = 0.
177 recip_Bo(i,j,bi,bj) = 0.
178 ENDIF
179 ENDDO
180 ENDDO
181 ENDIF
182 ENDDO
183 ENDDO
184 ELSE
185 STOP 'INI_LINEAR_PHISURF: We should never reach this point!'
186 ENDIF
187
188 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
189
190 C-- Update overlap regions (jmc: is it really needed ?)
191 c _EXCH_XY_RL(Bo_surf, myThid)
192 c _EXCH_XY_RL(recip_Bo, myThid)
193
194 IF ( usingPCoords .AND. .NOT.uniformLin_PhiSurf ) THEN
195 CALL WRITE_FLD_XY_RL( 'Bo_surf',' ',Bo_surf,0,myThid)
196 ENDIF
197
198 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
199
200 C-- Initialise phi0surf: used for atmos. surf. P-loading (ocean, z-coord)
201 C or topographic geopotential anom. (p-coord)
202
203 DO bj=myByLo(myThid),myByHi(myThid)
204 DO bi=myBxLo(myThid),myBxHi(myThid)
205 DO j=1-OLy,sNy+OLy
206 DO i=1-OLx,sNx+OLx
207 phi0surf(i,j,bi,bj) = 0.
208 ENDDO
209 ENDDO
210 ENDDO
211 ENDDO
212
213 IF ( fluidIsAir .AND. topoFile.NE.' ' ) THEN
214
215 #ifdef ALLOW_AUTODIFF
216 STOP 'CANNOT PRESENTLY USE THIS OPTION WITH ADJOINT'
217 #else
218
219 C-- Compute topoH = PhiRef(Po_surf)/g ; is different from original
220 C topoZ(read from file) because of truncation of Po_surf.
221 C NOTE: not clear for now which topoZ needs to be saved in common block
222 C-- AND set phi0surf = starting point for integrating Geopotential;
223
224 CALL INI_P_GROUND( -2,
225 O topoHloc,
226 I Ro_surf, myThid )
227
228 IF (selectFindRoSurf.NE.0) THEN
229 _EXCH_XY_RS(phi0surf, myThid)
230 CALL WRITE_FLD_XY_RS( 'phi0surf',' ',phi0surf,0,myThid)
231 ENDIF
232
233 CALL WRITE_FLD_XY_RS( 'topo_H',' ',topoHloc,0,myThid)
234
235 #endif /* ALLOW_AUTODIFF */
236
237 ENDIF
238
239 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
240 RETURN
241 END

  ViewVC Help
Powered by ViewVC 1.1.22