/[MITgcm]/MITgcm/verification/tutorial_global_oce_optim/code_ad/external_forcing_surf.F
ViewVC logotype

Contents of /MITgcm/verification/tutorial_global_oce_optim/code_ad/external_forcing_surf.F

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


Revision 1.4 - (show annotations) (download)
Sun Sep 5 22:32:04 2010 UTC (13 years, 9 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62k, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.3: +18 -2 lines
update after changing standard version
 (option for ptracer to convert Salt Relax into additional EmP)

1 C $Header: /u/gcmpack/MITgcm/model/src/external_forcing_surf.F,v 1.49 2009/12/21 00: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_PARAMS.h"
33 #include "SEAICE.h"
34 #endif /* ALLOW_SEAICE */
35 #ifdef ALLOW_SHELFICE
36 #include "SHELFICE.h"
37 #endif /* ALLOW_SHELFICE */
38
39 C !INPUT/OUTPUT PARAMETERS:
40 C === Routine arguments ===
41 C bi,bj :: tile indices
42 C iMin,iMax, jMin,jMax :: Range of points for calculation
43 C myTime :: Current time in simulation
44 C myIter :: Current iteration number in simulation
45 C myThid :: Thread no. that called this routine.
46 INTEGER bi,bj
47 INTEGER iMin, iMax
48 INTEGER jMin, jMax
49 _RL myTime
50 INTEGER myIter
51 INTEGER myThid
52
53 C !LOCAL VARIABLES:
54 C === Local variables ===
55 C i,j :: loop indices
56 C ks :: index of surface interface layer
57 INTEGER i,j
58 INTEGER ks
59 CEOP
60 #ifdef ALLOW_PTRACERS
61 C relaxForcingS :: Salt forcing due to surface relaxation
62 _RL relaxForcingS(1-OLx:sNx+OLx,1-OLy:sNy+OLy)
63 #endif /* ALLOW_PTRACERS */
64 #ifdef ALLOW_DIAGNOSTICS
65 _RL tmpFac
66 #endif /* ALLOW_DIAGNOSTICS */
67
68 IF ( usingPCoords ) THEN
69 ks = Nr
70 ELSE
71 ks = 1
72 ENDIF
73
74 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
75
76 IF ( doThetaClimRelax .OR. doSaltClimRelax ) THEN
77 C-- Start with surface restoring term :
78
79 #ifdef ALLOW_SEAICE
80 IF ( useSEAICE .AND. (.NOT. SEAICErestoreUnderIce) ) THEN
81 C Do not restore under sea-ice
82 DO j = jMin, jMax
83 DO i = iMin, iMax
84 C Heat Flux (restoring term) :
85 surfaceForcingT(i,j,bi,bj) =
86 & -lambdaThetaClimRelax(i,j,bi,bj)*(1.-AREA(i,j,bi,bj))
87 & *(theta(i,j,ks,bi,bj)-SST(i,j,bi,bj))
88 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
89 C Salt Flux (restoring term) :
90 surfaceForcingS(i,j,bi,bj) =
91 & -lambdaSaltClimRelax(i,j,bi,bj) *(1.-AREA(i,j,bi,bj))
92 & *(salt(i,j,ks,bi,bj)-SSS(i,j,bi,bj))
93 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
94 ENDDO
95 ENDDO
96 ELSE
97 #endif /* ALLOW_SEAICE */
98 DO j = jMin, jMax
99 DO i = iMin, iMax
100 C Heat Flux (restoring term) :
101 surfaceForcingT(i,j,bi,bj) =
102 & -lambdaThetaClimRelax(i,j,bi,bj)
103 & *(theta(i,j,ks,bi,bj)-SST(i,j,bi,bj))
104 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
105 C Salt Flux (restoring term) :
106 surfaceForcingS(i,j,bi,bj) =
107 & -lambdaSaltClimRelax(i,j,bi,bj)
108 & *(salt(i,j,ks,bi,bj)-SSS(i,j,bi,bj))
109 & *drF(ks)*_hFacC(i,j,ks,bi,bj)
110 ENDDO
111 ENDDO
112 #ifdef ALLOW_SEAICE
113 ENDIF
114 #endif /* ALLOW_SEAICE */
115
116 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
117 #ifdef NONLIN_FRSURF
118 C- T,S surface forcing will be applied (thermodynamics) after the update
119 C of surf.thickness (hFac): account for change in surf.thickness
120 IF (staggerTimeStep.AND.nonlinFreeSurf.GT.0) THEN
121 IF ( select_rStar.GT.0 ) THEN
122 # ifndef DISABLE_RSTAR_CODE
123 DO j=jMin,jMax
124 DO i=iMin,iMax
125 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
126 & * rStarExpC(i,j,bi,bj)
127 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
128 & * rStarExpC(i,j,bi,bj)
129 ENDDO
130 ENDDO
131 # endif /* DISABLE_RSTAR_CODE */
132 ELSE
133 DO j=jMin,jMax
134 DO i=iMin,iMax
135 IF (ks.EQ.ksurfC(i,j,bi,bj)) THEN
136 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
137 & *_recip_hFacC(i,j,ks,bi,bj)*hFac_surfC(i,j,bi,bj)
138 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
139 & *_recip_hFacC(i,j,ks,bi,bj)*hFac_surfC(i,j,bi,bj)
140 ENDIF
141 ENDDO
142 ENDDO
143 ENDIF
144 ENDIF
145 #endif /* NONLIN_FRSURF */
146
147 #ifdef ALLOW_DIAGNOSTICS
148 IF ( useDiagnostics ) THEN
149
150 C tRelax (temperature relaxation [W/m2], positive <-> increasing Theta)
151 tmpFac = HeatCapacity_Cp*rUnit2mass
152 CALL DIAGNOSTICS_SCALE_FILL(
153 & surfaceForcingT(1-OLx,1-OLy,bi,bj),tmpFac,1,
154 & 'TRELAX ',0, 1,2,bi,bj,myThid)
155
156 C sRelax (salt relaxation [g/m2/s], positive <-> increasing Salt)
157 tmpFac = rUnit2mass
158 CALL DIAGNOSTICS_SCALE_FILL(
159 & surfaceForcingS(1-OLx,1-OLy,bi,bj),tmpFac,1,
160 & 'SRELAX ',0, 1,2,bi,bj,myThid)
161
162 ENDIF
163 #endif /* ALLOW_DIAGNOSTICS */
164
165 ELSE
166 C-- No restoring for T & S : set surfaceForcingT,S to zero :
167
168 DO j = jMin, jMax
169 DO i = iMin, iMax
170 surfaceForcingT(i,j,bi,bj) = 0. _d 0
171 surfaceForcingS(i,j,bi,bj) = 0. _d 0
172 ENDDO
173 ENDDO
174
175 C-- end restoring / no restoring block.
176 ENDIF
177
178 #ifdef ALLOW_PTRACERS
179 IF ( usePTRACERS ) THEN
180 C-- save salt forcing due to surface relaxation
181 DO j = jMin, jMax
182 DO i = iMin, iMax
183 relaxForcingS(i,j) = surfaceForcingS(i,j,bi,bj)
184 ENDDO
185 ENDDO
186 ENDIF
187 #endif /* ALLOW_PTRACERS */
188
189 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
190
191 C-- Surface Fluxes :
192
193 DO j = jMin, jMax
194 DO i = iMin, iMax
195
196 C Zonal wind stress fu:
197 surfaceForcingU(i,j,bi,bj) =
198 & fu(i,j,bi,bj)*mass2rUnit
199 C Meridional wind stress fv:
200 surfaceForcingV(i,j,bi,bj) =
201 & fv(i,j,bi,bj)*mass2rUnit
202 C Net heat flux Qnet:
203 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
204 & - ( Qnet(i,j,bi,bj)
205 #ifdef SHORTWAVE_HEATING
206 & -Qsw(i,j,bi,bj)
207 #endif
208 #ifdef ALLOW_HFLUXM_CONTROL
209 & +Qnetm(i,j,bi,bj)
210 #endif
211 & ) *recip_Cp*mass2rUnit
212 C Net Salt Flux :
213 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
214 & -saltFlux(i,j,bi,bj)*mass2rUnit
215
216 ENDDO
217 ENDDO
218
219 #ifdef ALLOW_SALT_PLUME
220 C saltPlume is the amount of salt rejected by ice while freezing;
221 C it is here subtracted from surfaceForcingS and will be redistributed
222 C to multiple vertical levels later on as per Duffy et al. (GRL 1999)
223 IF ( useSALT_PLUME ) THEN
224 CALL SALT_PLUME_FORCING_SURF(
225 I bi, bj, iMin, iMax, jMin, jMax,
226 I myTime,myIter,myThid )
227 ENDIF
228 #endif /* ALLOW_SALT_PLUME */
229
230 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
231 C-- Fresh-water flux
232
233 C- Apply mask on Fresh-Water flux
234 C (needed for SSH forcing, whether or not exactConserv is used)
235 IF ( useRealFreshWaterFlux ) THEN
236 DO j=1-OLy,sNy+OLy
237 DO i=1-OLx,sNx+OLx
238 EmPmR(i,j,bi,bj) = EmPmR(i,j,bi,bj)*maskInC(i,j,bi,bj)
239 ENDDO
240 ENDDO
241 ENDIF
242
243 #ifdef EXACT_CONSERV
244 C NB: synchronous time step: PmEpR lag 1 time step behind EmPmR
245 C to stay consitent with volume change (=d/dt etaH).
246 IF ( staggerTimeStep ) THEN
247 DO j=1-OLy,sNy+OLy
248 DO i=1-OLx,sNx+OLx
249 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
250 ENDDO
251 ENDDO
252 ENDIF
253
254 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
255 & .AND. useRealFreshWaterFlux ) THEN
256
257 C-- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
258 C the water column height ; temp., salt, (tracer) flux associated
259 C with this input/output of water is added here to the surface tendency.
260
261 IF (temp_EvPrRn.NE.UNSET_RL) THEN
262 DO j = jMin, jMax
263 DO i = iMin, iMax
264 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
265 & + PmEpR(i,j,bi,bj)
266 & *( temp_EvPrRn - theta(i,j,ks,bi,bj) )
267 & *mass2rUnit
268 ENDDO
269 ENDDO
270 ENDIF
271
272 IF (salt_EvPrRn.NE.UNSET_RL) THEN
273 DO j = jMin, jMax
274 DO i = iMin, iMax
275 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
276 & + PmEpR(i,j,bi,bj)
277 & *( salt_EvPrRn - salt(i,j,ks,bi,bj) )
278 & *mass2rUnit
279 ENDDO
280 ENDDO
281 ENDIF
282
283 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
284 ELSE
285 #else /* EXACT_CONSERV */
286 IF (.TRUE.) THEN
287 #endif /* EXACT_CONSERV */
288
289 C-- EmPmR does not really affect the water column height (for tracer budget)
290 C and is converted to a salt tendency.
291
292 IF (convertFW2Salt .EQ. -1.) THEN
293 C- use local surface tracer field to calculate forcing term:
294
295 IF (temp_EvPrRn.NE.UNSET_RL) THEN
296 C account for Rain/Evap heat content (temp_EvPrRn) using local SST
297 DO j = jMin, jMax
298 DO i = iMin, iMax
299 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
300 & + EmPmR(i,j,bi,bj)
301 & *( theta(i,j,ks,bi,bj) - temp_EvPrRn )
302 & *mass2rUnit
303 ENDDO
304 ENDDO
305 ENDIF
306 IF (salt_EvPrRn.NE.UNSET_RL) THEN
307 C converts EmPmR to salinity tendency using surface local salinity
308 DO j = jMin, jMax
309 DO i = iMin, iMax
310 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
311 & + EmPmR(i,j,bi,bj)
312 & *( salt(i,j,ks,bi,bj) - salt_EvPrRn )
313 & *mass2rUnit
314 ENDDO
315 ENDDO
316 ENDIF
317
318 ELSE
319 C- use uniform tracer value to calculate forcing term:
320
321 IF (temp_EvPrRn.NE.UNSET_RL) THEN
322 C account for Rain/Evap heat content (temp_EvPrRn) assuming uniform SST (=tRef)
323 DO j = jMin, jMax
324 DO i = iMin, iMax
325 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
326 & + EmPmR(i,j,bi,bj)
327 & *( tRef(ks) - temp_EvPrRn )
328 & *mass2rUnit
329 ENDDO
330 ENDDO
331 ENDIF
332 IF (salt_EvPrRn.NE.UNSET_RL) THEN
333 C converts EmPmR to virtual salt flux using uniform salinity (default=35)
334 DO j = jMin, jMax
335 DO i = iMin, iMax
336 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
337 & + EmPmR(i,j,bi,bj)
338 & *( convertFW2Salt - salt_EvPrRn )
339 & *mass2rUnit
340 ENDDO
341 ENDDO
342 ENDIF
343
344 C- end local-surface-tracer / uniform-value distinction
345 ENDIF
346
347 ENDIF
348
349 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
350
351 #ifdef ALLOW_PTRACERS
352 IF ( usePTRACERS ) THEN
353 CALL PTRACERS_FORCING_SURF(
354 I relaxForcingS,
355 I bi, bj, iMin, iMax, jMin, jMax,
356 I myTime,myIter,myThid )
357 ENDIF
358 #endif /* ALLOW_PTRACERS */
359
360 #ifdef ATMOSPHERIC_LOADING
361 C-- Atmospheric surface Pressure loading : added to phi0surf when using Z-coord;
362 C Not yet implemented for Ocean in P: would need to be applied to the other end
363 C of the column, as a vertical velocity (omega); (meaningless for Atmos in P).
364 C- Note:
365 C Using P-coord., a hack (now directly applied from S/R INI_FORCING)
366 C is sometime used to read phi0surf from a file (pLoadFile) instead
367 C of computing it from bathymetry & density ref. profile.
368
369 IF ( usingZCoords ) THEN
370 C The true atmospheric P-loading is not yet implemented for P-coord
371 C (requires time varying dP(Nr) like dP(k-bottom) with NonLin FS).
372 IF ( useRealFreshWaterFlux ) THEN
373 DO j = jMin, jMax
374 DO i = iMin, iMax
375 phi0surf(i,j,bi,bj) = ( pLoad(i,j,bi,bj)
376 & +sIceLoad(i,j,bi,bj)*gravity
377 & )*recip_rhoConst
378 ENDDO
379 ENDDO
380 ELSE
381 DO j = jMin, jMax
382 DO i = iMin, iMax
383 phi0surf(i,j,bi,bj) = pLoad(i,j,bi,bj)*recip_rhoConst
384 ENDDO
385 ENDDO
386 ENDIF
387 c ELSEIF ( usingPCoords ) THEN
388 C-- This is a hack used to read phi0surf from a file (pLoadFile)
389 C instead of computing it from bathymetry & density ref. profile.
390 C ==> now done only once, in S/R INI_FORCING
391 c DO j = jMin, jMax
392 c DO i = iMin, iMax
393 c phi0surf(i,j,bi,bj) = pLoad(i,j,bi,bj)
394 c ENDDO
395 c ENDDO
396 ENDIF
397 #endif /* ATMOSPHERIC_LOADING */
398
399 #ifdef ALLOW_SHELFICE
400 IF ( usingZCoords ) THEN
401 IF ( useSHELFICE) THEN
402 DO j = jMin, jMax
403 DO i = iMin, iMax
404 phi0surf(i,j,bi,bj) = phi0surf(i,j,bi,bj)
405 & + shelficeLoadAnomaly(i,j,bi,bj)*recip_rhoConst
406 ENDDO
407 ENDDO
408 ENDIF
409 ENDIF
410 #endif /* ALLOW_SHELFICE */
411
412 #ifdef ALLOW_EBM
413 c-- Values for surfaceForcingT, surfaceForcingS
414 c are overwritten by those produced by EBM
415 cph AD recomputation problems if these IF useEBM are used
416 cph IF ( useEBM ) THEN
417 CALL EBM_FORCING_SURF(
418 I bi, bj, iMin, iMax, jMin, jMax,
419 I myTime,myIter,myThid )
420 cph ENDIF
421 #endif
422
423 RETURN
424 END

  ViewVC Help
Powered by ViewVC 1.1.22