/[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.17 - (show annotations) (download)
Thu Dec 17 23:47:06 2009 UTC (14 years, 5 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62, checkpoint62b
Changes since 1.16: +66 -5 lines
define 2-D "interior" masks (C,W & S); move global area computation from
ini_masks_etc.F to ini_linear_phisurf.F (called after packages_init_fixed)

1 C $Header: /u/gcmpack/MITgcm/model/src/ini_linear_phisurf.F,v 1.16 2009/06/14 21:50:26 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 | Compute global domain Area ;
18 C | Initialise -Boyancy at surface level (Bo_surf)
19 C | to setup the Linear relation: Phi_surf(eta)=Bo_surf*eta
20 C | Initialise phi0surf = starting point for integrating
21 C | phiHyd (= phiHyd at r=RoSurf)
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 #ifdef ALLOW_EXCH2
34 # include "W2_EXCH2_SIZE.h"
35 # include "W2_EXCH2_TOPOLOGY.h"
36 #endif /* ALLOW_EXCH2 */
37
38
39 C !INPUT/OUTPUT PARAMETERS:
40 C === Routine arguments ===
41 C myThid - Thread no. that called this routine.
42 INTEGER myThid
43
44 C == Local variables in common ==
45 C topoHloc had to be in common for multi threading but no longer
46 C needed since MDSIO now allows (2009/06/07) to write local arrays
47 _RL tileArea(nSx,nSy), threadArea
48 C put tileArea in (local) common block to print from master-thread:
49 COMMON / LOCAL_INI_PHISURF / tileArea
50
51 C !LOCAL VARIABLES:
52 C === Local variables ===
53 C topoHloc :: Temporary array used to write surface topography
54 C bi,bj :: tile indices
55 C I,J,K :: Loop counters
56 _RS topoHloc(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
57 INTEGER bi, bj
58 INTEGER I, J, K
59 _RL pLoc, rhoLoc
60 _RL dPIdp
61 CHARACTER*(MAX_LEN_MBUF) msgBuf
62 CEOP
63
64 #ifdef ALLOW_AUTODIFF_TAMC
65 DO bj=myByLo(myThid),myByHi(myThid)
66 DO bi=myBxLo(myThid),myBxHi(myThid)
67 DO J=1-Oly,sNy+Oly
68 DO I=1-Olx,sNx+Olx
69 Bo_surf(I,J,bi,bj) = 0. _d 0
70 recip_Bo(I,J,bi,bj) = 0. _d 0
71 ENDDO
72 ENDDO
73 ENDDO
74 ENDDO
75 #endif
76
77 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
78
79 C Calculate global domain area:
80 C use to be in ini_masks_etc.F but has been move after packages_init_fixed
81 C in case 1 pkg (e.g., OBCS) modifies the domain size.
82 threadArea = 0. _d 0
83 DO bj = myByLo(myThid), myByHi(myThid)
84 DO bi = myBxLo(myThid), myBxHi(myThid)
85 C- Compute the domain Area:
86 tileArea(bi,bj) = 0. _d 0
87 DO j=1,sNy
88 DO i=1,sNx
89 tileArea(bi,bj) = tileArea(bi,bj)
90 & + rA(i,j,bi,bj)*maskInC(i,j,bi,bj)
91 c & + rA(i,j,bi,bj)*maskH(i,j,bi,bj)
92 ENDDO
93 ENDDO
94 c threadArea = threadArea + tileArea(bi,bj)
95 ENDDO
96 ENDDO
97 c#ifdef ALLOW_AUTODIFF_TAMC
98 C_jmc: apply GLOBAL_SUM to thread-local variable (not in common block)
99 c _GLOBAL_SUM_RL( threadArea, myThid )
100 c#else
101 CALL GLOBAL_SUM_TILE_RL( tileArea, threadArea, myThid )
102 c#endif
103 _BEGIN_MASTER( myThid )
104 globalArea = threadArea
105 C- list empty tiles:
106 msgBuf(1:1) = ' '
107 DO bj = 1,nSy
108 DO bi = 1,nSx
109 IF ( tileArea(bi,bj).EQ.0. _d 0 ) THEN
110 #ifdef ALLOW_EXCH2
111 WRITE(msgBuf,'(A,I6,A,2I4,A)')
112 & 'Empty tile: #', W2_myTileList(bi,bj), ' (bi,bj=',bi,bj,' )'
113 #else
114 WRITE(msgBuf,'(A,I6,I6)') 'Empty tile bi,bj=', bi, bj
115 #endif
116 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
117 & SQUEEZE_RIGHT, myThid )
118 ENDIF
119 ENDDO
120 ENDDO
121 IF ( msgBuf(1:1).NE.' ' ) THEN
122 WRITE(msgBuf,'(A)') ' '
123 CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
124 & SQUEEZE_RIGHT, myThid )
125 ENDIF
126 _END_MASTER( myThid )
127
128 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
129
130 C-- Initialise -Boyancy at surface level : Bo_surf
131 C Bo_surf is defined as d/dr(Phi_surf) and set to g/z2rUnit with
132 C z2rUnit = conversion factor from z-unit to r-unit: [z] * z2rUnit = [r]
133 C an accurate formulation includes P_surf and T,S_ref effects on rho_surf:
134 C (setting uniformLin_PhiSurf=.FALSE.):
135 C z-coord (z2rUnit=1): Bo_surf = - Boyancy
136 C = g * rho_surf(Tref,Sref,pSurf_0)/rho_0
137 C p-coord (z2rUnit=rho*g): Bo_surf = 1/rho(Tref(ksurf),pSurf_0)
138 C Note: on Phi_surf splitting : Non-linear Time-dependent effects on B_surf
139 C [through eta & (T-tRef)_surf] are included in PhiHyd rather than in Bo_surf
140 C--
141 IF ( buoyancyRelation .EQ. 'OCEANIC' ) THEN
142 C- gBaro = gravity (except for External mode test with reduced gravity)
143 DO bj=myByLo(myThid),myByHi(myThid)
144 DO bi=myBxLo(myThid),myBxHi(myThid)
145 DO J=1-Oly,sNy+Oly
146 DO I=1-Olx,sNx+Olx
147 Bo_surf(I,J,bi,bj) = gBaro
148 recip_Bo(I,J,bi,bj) = 1. _d 0 / gBaro
149 ENDDO
150 ENDDO
151 ENDDO
152 ENDDO
153 ELSEIF ( uniformLin_PhiSurf ) THEN
154 C- use a linear (in ps) uniform relation : Phi'_surf = 1/rhoConst * ps'_surf
155 DO bj=myByLo(myThid),myByHi(myThid)
156 DO bi=myBxLo(myThid),myBxHi(myThid)
157 DO J=1-Oly,sNy+Oly
158 DO I=1-Olx,sNx+Olx
159 c Bo_surf(I,J,bi,bj) = rVel2wUnit(1)*gravity
160 c recip_Bo(I,J,bi,bj) = wUnit2rVel(1)*recip_gravity
161 Bo_surf(I,J,bi,bj) = recip_rhoConst
162 recip_Bo(I,J,bi,bj) = rhoConst
163 ENDDO
164 ENDDO
165 ENDDO
166 ENDDO
167 ELSEIF ( buoyancyRelation .EQ. 'OCEANICP' ) THEN
168 DO bj=myByLo(myThid),myByHi(myThid)
169 DO bi=myBxLo(myThid),myBxHi(myThid)
170 DO J=1-Oly,sNy+Oly
171 DO I=1-Olx,sNx+Olx
172 IF ( Ro_surf(I,J,bi,bj).GT.0. _d 0
173 & .AND. ksurfC(I,J,bi,bj).LE.Nr ) THEN
174 k = ksurfC(I,J,bi,bj)
175 pLoc = Ro_surf(I,J,bi,bj)
176 CALL FIND_RHO_SCALAR(
177 I tRef(k), sRef(k), pLoc,
178 O rhoLoc, myThid )
179 IF ( rhoLoc .EQ. 0. _d 0 ) THEN
180 Bo_surf(I,J,bi,bj) = 0. _d 0
181 ELSE
182 Bo_surf(I,J,bi,bj) = 1. _d 0/rhoLoc
183 ENDIF
184 recip_Bo(I,J,bi,bj) = rhoLoc
185 ELSE
186 Bo_surf(I,J,bi,bj) = 0. _d 0
187 recip_Bo(I,J,bi,bj) = 0. _d 0
188 ENDIF
189 ENDDO
190 ENDDO
191 ENDDO
192 ENDDO
193 ELSEIF ( buoyancyRelation .EQ. 'ATMOSPHERIC' ) THEN
194 C- use a linearized (in ps) Non-uniform relation : Bo_surf(Po_surf,tRef_surf)
195 C--- Bo = d/d_p(Phi_surf) = tRef_surf*d/d_p(PI) ; PI = Cp*(p/Po)^kappa
196 DO bj=myByLo(myThid),myByHi(myThid)
197 DO bi=myBxLo(myThid),myBxHi(myThid)
198 DO J=1-Oly,sNy+Oly
199 DO I=1-Olx,sNx+Olx
200 IF ( Ro_surf(I,J,bi,bj).GT.0. _d 0
201 & .AND. ksurfC(I,J,bi,bj).LE.Nr ) THEN
202 dPIdp = (atm_Cp*atm_kappa/atm_Po)*
203 & (Ro_surf(I,J,bi,bj)/atm_Po)**(atm_kappa-1. _d 0)
204 Bo_surf(I,J,bi,bj) = dPIdp*tRef(ksurfC(I,J,bi,bj))
205 recip_Bo(I,J,bi,bj) = 1. _d 0 / Bo_surf(I,J,bi,bj)
206 ELSE
207 Bo_surf(I,J,bi,bj) = 0.
208 recip_Bo(I,J,bi,bj) = 0.
209 ENDIF
210 ENDDO
211 ENDDO
212 ENDDO
213 ENDDO
214 ELSE
215 STOP 'INI_LINEAR_PHISURF: We should never reach this point!'
216 ENDIF
217
218 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
219
220 C-- Update overlap regions (jmc: is it really needed ?)
221 _EXCH_XY_RL(Bo_surf, myThid)
222 _EXCH_XY_RL(recip_Bo, myThid)
223
224 IF ( ( buoyancyRelation .EQ. 'ATMOSPHERIC' .OR.
225 & buoyancyRelation .EQ. 'OCEANICP' )
226 & .AND. .NOT.uniformLin_PhiSurf ) THEN
227
228 CALL WRITE_FLD_XY_RL( 'Bo_surf',' ',Bo_surf,0,myThid)
229
230 ENDIF
231
232 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
233
234 C-- Initialise phi0surf: used for atmos. surf. P-loading (ocean, z-coord)
235 C or topographic geopotential anom. (p-coord)
236
237 DO bj=myByLo(myThid),myByHi(myThid)
238 DO bi=myBxLo(myThid),myBxHi(myThid)
239 DO J=1-Oly,sNy+Oly
240 DO I=1-Olx,sNx+Olx
241 phi0surf(I,J,bi,bj) = 0.
242 ENDDO
243 ENDDO
244 ENDDO
245 ENDDO
246
247 IF ( buoyancyRelation .EQ. 'ATMOSPHERIC'
248 & .AND. topoFile.NE.' ' ) THEN
249
250 #ifdef ALLOW_AUTODIFF_TAMC
251 STOP 'CANNOT PRESENTLY USE THIS OPTION WITH ADJOINT'
252 #else
253
254 C-- Compute topoH = PhiRef(Po_surf)/g ; is different from original
255 C topoZ(read from file) because of truncation of Po_surf.
256 C NOTE: not clear for now which topoZ needs to be saved in common block
257 C-- AND set phi0surf = starting point for integrating Geopotential;
258
259 CALL INI_P_GROUND( -2,
260 O topoHloc,
261 I Ro_surf, myThid )
262
263
264 IF (selectFindRoSurf.NE.0) THEN
265 _EXCH_XY_RS(phi0surf, myThid)
266 CALL WRITE_FLD_XY_RS( 'phi0surf',' ',phi0surf,0,myThid)
267 ENDIF
268
269 CALL WRITE_FLD_XY_RS( 'topo_H',' ',topoHloc,0,myThid)
270
271 #endif /* ALLOW_AUTODIFF_TAMC */
272
273 ENDIF
274
275 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
276 RETURN
277 END

  ViewVC Help
Powered by ViewVC 1.1.22