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

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

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


Revision 1.35 - (show annotations) (download)
Wed Jun 7 01:55:13 2006 UTC (18 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58m_post, checkpoint58k_post, checkpoint58l_post, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post
Changes since 1.34: +7 -7 lines
Modifications for bottom topography control
o replace hFacC by _hFacC at various places
o replace ALLOW_HFACC_CONTROL by ALLOW_DEPTH_CONTROL
o add non-self-adjoint cg2d_nsa
o update autodiff support routines
o re-initialise hfac after ctrl_depth_ini
o works for 5x5 box, doesnt work for global_ocean.90x40x15

1 C $Header: /u/gcmpack/MITgcm/model/src/external_forcing_surf.F,v 1.34 2006/03/02 21:24:58 jmc Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6
7 CBOP
8 C !ROUTINE: EXTERNAL_FORCING_SURF
9 C !INTERFACE:
10 SUBROUTINE EXTERNAL_FORCING_SURF(
11 I bi, bj, iMin, iMax, jMin, jMax,
12 I myTime, myIter, myThid )
13 C !DESCRIPTION: \bv
14 C *==========================================================*
15 C | SUBROUTINE EXTERNAL_FORCING_SURF
16 C | o Determines forcing terms based on external fields
17 C | relaxation terms etc.
18 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 "FFIELDS.h"
28 #include "DYNVARS.h"
29 #include "GRID.h"
30 #include "SURFACE.h"
31 #ifdef ALLOW_SEAICE
32 #include "SEAICE.h"
33 #endif /* ALLOW_SEAICE */
34 #ifdef ALLOW_SHELFICE
35 #include "SHELFICE.h"
36 #endif /* ALLOW_SHELFICE */
37 C !INPUT/OUTPUT PARAMETERS:
38 C === Routine arguments ===
39 C bi,bj :: tile indices
40 C iMin,iMax, jMin,jMax :: Range of points for calculation
41 C myTime :: Current time in simulation
42 C myIter :: Current iteration number in simulation
43 C myThid :: Thread no. that called this routine.
44 _RL myTime
45 INTEGER myIter
46 INTEGER myThid
47 INTEGER bi,bj
48 INTEGER iMin, iMax
49 INTEGER jMin, jMax
50
51 C !LOCAL VARIABLES:
52 C === Local variables ===
53 INTEGER i,j
54 C number of surface interface layer
55 INTEGER ks
56 #ifdef ALLOW_DIAGNOSTICS
57 _RL tmpFac
58 #endif /* ALLOW_DIAGNOSTICS */
59 CEOP
60
61 IF ( usingPCoords ) THEN
62 ks = Nr
63 ELSE
64 ks = 1
65 ENDIF
66
67 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
68
69 IF ( doThetaClimRelax .OR. doSaltClimRelax ) THEN
70 C-- Start with surface restoring term :
71
72 DO j = jMin, jMax
73 DO i = iMin, iMax
74 #ifdef ALLOW_SEAICE
75 C Do not restore under sea-ice
76 C Heat Flux (restoring term) :
77 surfaceForcingT(i,j,bi,bj) =
78 & -lambdaThetaClimRelax(i,j,bi,bj) * (1-AREA(i,j,1,bi,bj))
79 & *(theta(i,j,ks,bi,bj)-SST(i,j,bi,bj))
80 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
81 C Salt Flux (restoring term) :
82 surfaceForcingS(i,j,bi,bj) =
83 & -lambdaSaltClimRelax(i,j,bi,bj) * (1-AREA(i,j,1,bi,bj))
84 & *(salt(i,j,ks,bi,bj)-SSS(i,j,bi,bj))
85 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
86 #else /* ifndef ALLOW_SEAICE */
87 C Heat Flux (restoring term) :
88 surfaceForcingT(i,j,bi,bj) =
89 & -lambdaThetaClimRelax(i,j,bi,bj)
90 & *(theta(i,j,ks,bi,bj)-SST(i,j,bi,bj))
91 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
92 C Salt Flux (restoring term) :
93 surfaceForcingS(i,j,bi,bj) =
94 & -lambdaSaltClimRelax(i,j,bi,bj)
95 & *(salt(i,j,ks,bi,bj)-SSS(i,j,bi,bj))
96 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
97 #endif /* ALLOW_SEAICE */
98 ENDDO
99 ENDDO
100
101 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
102 #ifdef NONLIN_FRSURF
103 C- T,S surface forcing will be applied (thermodynamics) after the update
104 C of surf.thickness (hFac): account for change in surf.thickness
105 IF (staggerTimeStep.AND.nonlinFreeSurf.GT.0) THEN
106 IF (select_rStar.GT.0) THEN
107 # ifndef DISABLE_RSTAR_CODE
108 DO j=jMin,jMax
109 DO i=iMin,iMax
110 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
111 & * rStarExpC(i,j,bi,bj)
112 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
113 & * rStarExpC(i,j,bi,bj)
114 ENDDO
115 ENDDO
116 # endif /* DISABLE_RSTAR_CODE */
117 ELSE
118 DO j=jMin,jMax
119 DO i=iMin,iMax
120 IF (ks.EQ.ksurfC(i,j,bi,bj)) THEN
121 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
122 & *_recip_hFacC(i,j,ks,bi,bj)*hFac_surfC(i,j,bi,bj)
123 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
124 & *_recip_hFacC(i,j,ks,bi,bj)*hFac_surfC(i,j,bi,bj)
125 ENDIF
126 ENDDO
127 ENDDO
128 ENDIF
129 ENDIF
130 #endif /* NONLIN_FRSURF */
131
132 #ifdef ALLOW_DIAGNOSTICS
133 IF ( useDiagnostics ) THEN
134
135 C tRelax (temperature relaxation [W/m2], positive <-> increasing Theta)
136 tmpFac = HeatCapacity_Cp*recip_horiVertRatio*rhoConst
137 CALL DIAGNOSTICS_SCALE_FILL(
138 & surfaceForcingT(1-Olx,1-Oly,bi,bj),tmpFac,1,
139 & 'TRELAX ',0, 1,2,bi,bj,myThid)
140
141 C sRelax (salt relaxation [g/m2/s], positive <-> increasing Salt)
142 tmpFac = recip_horiVertRatio*rhoConst
143 CALL DIAGNOSTICS_SCALE_FILL(
144 & surfaceForcingS(1-Olx,1-Oly,bi,bj),tmpFac,1,
145 & 'SRELAX ',0, 1,2,bi,bj,myThid)
146
147 ENDIF
148 #endif /* ALLOW_DIAGNOSTICS */
149
150 ELSE
151 C-- No restoring for T & S : set surfaceForcingT,S to zero :
152
153 DO j = jMin, jMax
154 DO i = iMin, iMax
155 surfaceForcingT(i,j,bi,bj) = 0. _d 0
156 surfaceForcingS(i,j,bi,bj) = 0. _d 0
157 ENDDO
158 ENDDO
159
160 C-- end restoring / no restoring block.
161 ENDIF
162
163 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
164
165 C-- Surface Fluxes :
166
167 DO j = jMin, jMax
168 DO i = iMin, iMax
169
170 C Zonal wind stress fu:
171 surfaceForcingU(i,j,bi,bj) =
172 & fu(i,j,bi,bj)*horiVertRatio*recip_rhoConst
173 C Meridional wind stress fv:
174 surfaceForcingV(i,j,bi,bj) =
175 & fv(i,j,bi,bj)*horiVertRatio*recip_rhoConst
176 C Net heat flux Qnet:
177 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
178 & - ( Qnet(i,j,bi,bj)
179 #ifdef SHORTWAVE_HEATING
180 & -Qsw(i,j,bi,bj)
181 #endif
182 & ) *recip_Cp*horiVertRatio*recip_rhoConst
183 C Net Salt Flux :
184 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
185 & -saltFlux(i,j,bi,bj)*horiVertRatio*recip_rhoConst
186
187 ENDDO
188 ENDDO
189
190 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
191 C-- Fresh-water flux
192
193 C- Apply mask on Fresh-Water flux
194 C (needed for SSH forcing, whether or not exactConserv is used)
195 IF ( useRealFreshWaterFlux ) THEN
196 DO j=1,sNy
197 DO i=1,sNx
198 EmPmR(i,j,bi,bj) = EmPmR(i,j,bi,bj)*maskH(i,j,bi,bj)
199 ENDDO
200 ENDDO
201 ENDIF
202
203 #ifdef EXACT_CONSERV
204 c NB: synchronous time step: PmEpR lag 1 time step behind EmPmR
205 c to stay consitent with volume change (=d/dt etaH).
206 IF ( staggerTimeStep ) THEN
207 DO j=1,sNy
208 DO i=1,sNx
209 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
210 ENDDO
211 ENDDO
212 ENDIF
213
214 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
215 & .AND. useRealFreshWaterFlux ) THEN
216
217 c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
218 c the water column height ; temp., salt, (tracer) flux associated
219 c with this input/output of water is added here to the surface tendency.
220 c
221
222 IF (temp_EvPrRn.NE.UNSET_RL) THEN
223 DO j = jMin, jMax
224 DO i = iMin, iMax
225 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
226 & + PmEpR(i,j,bi,bj)
227 & *( temp_EvPrRn - theta(i,j,ks,bi,bj) )
228 & *convertEmP2rUnit
229 ENDDO
230 ENDDO
231 ENDIF
232
233 IF (salt_EvPrRn.NE.UNSET_RL) THEN
234 DO j = jMin, jMax
235 DO i = iMin, iMax
236 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
237 & + PmEpR(i,j,bi,bj)
238 & *( salt_EvPrRn - salt(i,j,ks,bi,bj) )
239 & *convertEmP2rUnit
240 ENDDO
241 ENDDO
242 ENDIF
243
244 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
245 ELSE
246 #else /* EXACT_CONSERV */
247 IF (.TRUE.) THEN
248 #endif /* EXACT_CONSERV */
249
250 c- EmPmR does not really affect the water column height (for tracer budget)
251 c and is converted to a salt tendency.
252
253 IF (convertFW2Salt .EQ. -1.) THEN
254 c- converts EmPmR to salinity tendency using surface local salinity
255 DO j = jMin, jMax
256 DO i = iMin, iMax
257 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
258 & + EmPmR(i,j,bi,bj)*salt(i,j,ks,bi,bj)
259 & *convertEmP2rUnit
260 ENDDO
261 ENDDO
262 ELSE
263 c- converts EmPmR to virtual salt flux using uniform salinity (default=35)
264 DO j = jMin, jMax
265 DO i = iMin, iMax
266 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
267 & + EmPmR(i,j,bi,bj)*convertFW2Salt
268 & *convertEmP2rUnit
269 ENDDO
270 ENDDO
271 ENDIF
272
273 ENDIF
274
275 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
276
277 #ifdef ALLOW_PTRACERS
278 IF ( usePTRACERS ) THEN
279 CALL PTRACERS_FORCING_SURF(
280 I bi, bj, iMin, iMax, jMin, jMax,
281 I myTime,myIter,myThid )
282 ENDIF
283 #endif /* ALLOW_PTRACERS */
284
285 #ifdef ATMOSPHERIC_LOADING
286
287 C-- Atmospheric surface Pressure loading :
288
289 IF ( usingZCoords ) THEN
290 IF ( useRealFreshWaterFlux ) THEN
291 DO j = jMin, jMax
292 DO i = iMin, iMax
293 phi0surf(i,j,bi,bj) = ( pload(i,j,bi,bj)
294 & +sIceLoad(i,j,bi,bj)*gravity
295 & )*recip_rhoConst
296 ENDDO
297 ENDDO
298 ELSE
299 DO j = jMin, jMax
300 DO i = iMin, iMax
301 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)*recip_rhoConst
302 ENDDO
303 ENDDO
304 ENDIF
305 ELSEIF ( usingPCoords ) THEN
306 C-- This is a hack used to read phi0surf from a file (ploadFile)
307 C instead of computing it from bathymetry & density ref. profile.
308 C The true atmospheric P-loading is not yet implemented for P-coord
309 C (requires time varying dP(Nr) like dP(k-bottom) with NonLin FS).
310 DO j = jMin, jMax
311 DO i = iMin, iMax
312 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)
313 ENDDO
314 ENDDO
315 ENDIF
316
317 #endif /* ATMOSPHERIC_LOADING */
318
319 #ifdef ALLOW_SHELFICE
320 IF ( usingZCoords ) THEN
321 IF ( useSHELFICE) THEN
322 DO j = jMin, jMax
323 DO i = iMin, iMax
324 phi0surf(i,j,bi,bj) = phi0surf(i,j,bi,bj)
325 & + shelficeLoadAnomaly(i,j,bi,bj)*recip_rhoConst
326 ENDDO
327 ENDDO
328 ENDIF
329 ENDIF
330 #endif /* ALLOW_SHELFICE */
331
332 #ifdef ALLOW_EBM
333 c-- Values for surfaceForcingT, surfaceForcingS
334 c are overwritten by those produced by EBM
335 cph AD recomputation problems if these IF useEBM are used
336 cph IF ( useEBM ) THEN
337 CALL EBM_FORCING_SURF(
338 I bi, bj, iMin, iMax, jMin, jMax,
339 I myTime,myIter,myThid )
340 cph ENDIF
341 #endif
342
343 RETURN
344 END

  ViewVC Help
Powered by ViewVC 1.1.22