/[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.64 - (show annotations) (download)
Sat Sep 17 17:00:05 2016 UTC (7 years, 7 months ago) by mmazloff
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, HEAD
Changes since 1.63: +4 -1 lines
Add empmr store for BLING package

1 C $Header: /u/gcmpack/MITgcm/model/src/external_forcing_surf.F,v 1.63 2014/05/21 21:48:32 heimbach Exp $
2 C $Name: $
3
4 #include "PACKAGES_CONFIG.h"
5 #include "CPP_OPTIONS.h"
6 #ifdef ALLOW_AUTODIFF
7 # include "AUTODIFF_OPTIONS.h"
8 #endif
9 #ifdef ALLOW_SALT_PLUME
10 # include "SALT_PLUME_OPTIONS.h"
11 #endif
12 #undef CHECK_OVERLAP_FORCING
13
14 CBOP
15 C !ROUTINE: EXTERNAL_FORCING_SURF
16 C !INTERFACE:
17 SUBROUTINE EXTERNAL_FORCING_SURF(
18 I iMin, iMax, jMin, jMax,
19 I myTime, myIter, myThid )
20 C !DESCRIPTION: \bv
21 C *==========================================================*
22 C | SUBROUTINE EXTERNAL_FORCING_SURF
23 C | o Determines forcing terms based on external fields
24 C | relaxation terms etc.
25 C *==========================================================*
26 C \ev
27
28 C !USES:
29 IMPLICIT NONE
30 C === Global variables ===
31 #include "SIZE.h"
32 #include "EEPARAMS.h"
33 #include "PARAMS.h"
34 #include "FFIELDS.h"
35 #include "DYNVARS.h"
36 #include "GRID.h"
37 #include "SURFACE.h"
38 #ifdef ALLOW_AUTODIFF
39 # include "tamc.h"
40 # include "tamc_keys.h"
41 #endif
42
43 C !INPUT/OUTPUT PARAMETERS:
44 C === Routine arguments ===
45 C iMin,iMax, jMin,jMax :: Range of points for calculation
46 C myTime :: Current time in simulation
47 C myIter :: Current iteration number in simulation
48 C myThid :: Thread no. that called this routine.
49 INTEGER iMin, iMax
50 INTEGER jMin, jMax
51 _RL myTime
52 INTEGER myIter
53 INTEGER myThid
54
55 C !LOCAL VARIABLES:
56 C === Local variables ===
57 C bi,bj :: tile indices
58 C i,j :: loop indices
59 C ks :: index of surface interface layer
60 INTEGER bi,bj
61 INTEGER i,j
62 INTEGER ks
63 _RL recip_Cp
64 #ifdef ALLOW_BALANCE_FLUXES
65 _RS tmpVar(1)
66 #endif
67 #ifdef CHECK_OVERLAP_FORCING
68 _RS fixVal
69 #endif
70 CEOP
71
72 IF ( usingPCoords ) THEN
73 ks = Nr
74 ELSE
75 ks = 1
76 ENDIF
77 recip_Cp = 1. _d 0 / HeatCapacity_Cp
78
79 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
80
81 C-- Apply adjustment (balancing forcing) and exchanges
82 C to oceanic surface forcing
83
84 #ifdef ALLOW_BALANCE_FLUXES
85 C balance fluxes
86 tmpVar(1) = oneRS
87 IF ( balanceEmPmR .AND. (.NOT.useSeaice .OR. useThSIce) ) THEN
88 CALL REMOVE_MEAN_RS( 1, EmPmR, maskInC, maskInC, rA, tmpVar,
89 & 'EmPmR', myTime, myThid )
90 ENDIF
91 IF ( balanceQnet .AND. (.NOT.useSeaice .OR. useThSIce) ) THEN
92 CALL REMOVE_MEAN_RS( 1, Qnet, maskInC, maskInC, rA, tmpVar,
93 & 'Qnet ', myTime, myThid )
94 ENDIF
95 #endif /* ALLOW_BALANCE_FLUXES */
96
97 C- Apply exchanges (if needed)
98
99 #ifdef CHECK_OVERLAP_FORCING
100 C Put large value in overlap of forcing array to check if exch is needed
101 c IF ( .NOT. useKPP ) THEN
102 fixVal = 1.
103 CALL RESET_HALO_RS ( EmPmR, fixVal, 1, myThid )
104 fixVal = 400.
105 CALL RESET_HALO_RS ( Qnet, fixVal, 1, myThid )
106 fixVal = -200.
107 CALL RESET_HALO_RS ( Qsw, fixVal, 1, myThid )
108 fixVal = 40.
109 CALL RESET_HALO_RS ( saltFlux, fixVal, 1, myThid )
110 c ENDIF
111 #endif /* CHECK_OVERLAP_FORCING */
112
113 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
114
115 #ifdef EXACT_CONSERV
116 C NB: synchronous time step: PmEpR lag 1 time step behind EmPmR
117 C to stay consitent with volume change (=d/dt etaH).
118 # ifdef ALLOW_AUTODIFF_TAMC
119 CADJ STORE PmEpR = comlev1, key = ikey_dynamics, kind = isbyte
120 CADJ STORE EmPmR = comlev1, key = ikey_dynamics, kind = isbyte
121 # endif
122 DO bj=myByLo(myThid),myByHi(myThid)
123 DO bi=myBxLo(myThid),myBxHi(myThid)
124 IF ( staggerTimeStep ) THEN
125 DO j=1-OLy,sNy+OLy
126 DO i=1-OLx,sNx+OLx
127 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
128 ENDDO
129 ENDDO
130 ENDIF
131 ENDDO
132 ENDDO
133 #endif /* EXACT_CONSERV */
134
135 C-- set surfaceForcingT,S to zero.
136 DO bj=myByLo(myThid),myByHi(myThid)
137 DO bi=myBxLo(myThid),myBxHi(myThid)
138 DO j=1-OLy,sNy+OLy
139 DO i=1-OLx,sNx+OLx
140 surfaceForcingT(i,j,bi,bj) = 0. _d 0
141 surfaceForcingS(i,j,bi,bj) = 0. _d 0
142 ENDDO
143 ENDDO
144 ENDDO
145 ENDDO
146
147 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
148
149 C-- Start with surface restoring term :
150 IF ( doThetaClimRelax .OR. doSaltClimRelax ) THEN
151 CALL FORCING_SURF_RELAX(
152 I iMin, iMax, jMin, jMax,
153 I myTime, myIter, myThid )
154 ENDIF
155
156 #ifdef ALLOW_PTRACERS
157 C-- passive tracer surface forcing:
158 #ifdef ALLOW_AUTODIFF_TAMC
159 CADJ STORE surfaceForcingS = comlev1, key = ikey_dynamics,
160 CADJ & kind = isbyte
161 #ifdef ALLOW_BLING
162 CADJ STORE EmPmR = comlev1, key = ikey_dynamics, kind = isbyte
163 #endif
164 #endif
165 IF ( usePTRACERS ) THEN
166 DO bj=myByLo(myThid),myByHi(myThid)
167 DO bi=myBxLo(myThid),myBxHi(myThid)
168 CALL PTRACERS_FORCING_SURF(
169 I surfaceForcingS(1-OLx,1-OLy,bi,bj),
170 I bi, bj, iMin, iMax, jMin, jMax,
171 I myTime, myIter, myThid )
172 ENDDO
173 ENDDO
174 ENDIF
175 #endif /* ALLOW_PTRACERS */
176
177 C- Notes: setting of PmEpR and pTracers surface forcing could have been
178 C moved below, inside a unique bi,bj block. However this results
179 C in tricky dependencies for TAF (and recomputations).
180 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
181
182 DO bj=myByLo(myThid),myByHi(myThid)
183 DO bi=myBxLo(myThid),myBxHi(myThid)
184
185 #ifdef ALLOW_AUTODIFF_TAMC
186 act1 = bi - myBxLo(myThid)
187 max1 = myBxHi(myThid) - myBxLo(myThid) + 1
188 act2 = bj - myByLo(myThid)
189 max2 = myByHi(myThid) - myByLo(myThid) + 1
190 act3 = myThid - 1
191 max3 = nTx*nTy
192 act4 = ikey_dynamics - 1
193 ikey = (act1 + 1) + act2*max1
194 & + act3*max1*max2
195 & + act4*max1*max2*max3
196 #endif /* ALLOW_AUTODIFF_TAMC */
197
198 #ifdef ALLOW_AUTODIFF_TAMC
199 CADJ STORE EmPmR(:,:,bi,bj) = comlev1_bibj, key=ikey, kind = isbyte
200 #ifdef EXACT_CONSERV
201 CADJ STORE PmEpR(:,:,bi,bj) = comlev1_bibj, key=ikey, kind = isbyte
202 #endif
203 #endif /* ALLOW_AUTODIFF_TAMC */
204
205 C-- Surface Fluxes :
206 DO j = jMin, jMax
207 DO i = iMin, iMax
208
209 C Zonal wind stress fu:
210 surfaceForcingU(i,j,bi,bj) = fu(i,j,bi,bj)*mass2rUnit
211 C Meridional wind stress fv:
212 surfaceForcingV(i,j,bi,bj) = fv(i,j,bi,bj)*mass2rUnit
213 C Net heat flux Qnet:
214 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
215 & - ( Qnet(i,j,bi,bj)
216 #ifdef SHORTWAVE_HEATING
217 & -Qsw(i,j,bi,bj)
218 #endif
219 & ) *recip_Cp*mass2rUnit
220 C Net Salt Flux :
221 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
222 & -saltFlux(i,j,bi,bj)*mass2rUnit
223
224 ENDDO
225 ENDDO
226
227 #ifdef ALLOW_SALT_PLUME
228 C saltPlume is the amount of salt rejected by ice while freezing;
229 C it is here subtracted from surfaceForcingS and will be redistributed
230 C to multiple vertical levels later on as per Duffy et al. (GRL 1999)
231 C-- for the case of SALT_PLUME_VOLUME, need to call this S/R right
232 C-- before kpp in do_oceanic_phys.F due to recent moved of
233 C-- external_forcing_surf.F outside bi,bj loop.
234 #ifndef SALT_PLUME_VOLUME
235 IF ( useSALT_PLUME ) THEN
236 CALL SALT_PLUME_FORCING_SURF(
237 I bi, bj, iMin, iMax, jMin, jMax,
238 I myTime, myIter, myThid )
239 ENDIF
240 #endif /* SALT_PLUME_VOLUME */
241 #endif /* ALLOW_SALT_PLUME */
242
243 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
244 C-- Fresh-water flux
245
246 C- Apply mask on Fresh-Water flux (if useRealFreshWaterFlux)
247 C <== removed: maskInC is applied directly in S/R SOLVE_FOR_PRESSURE
248
249 #ifdef EXACT_CONSERV
250 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
251 & .AND. useRealFreshWaterFlux ) THEN
252
253 C-- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
254 C the water column height ; temp., salt, (tracer) flux associated
255 C with this input/output of water is added here to the surface tendency.
256
257 IF (temp_EvPrRn.NE.UNSET_RL) THEN
258 DO j = jMin, jMax
259 DO i = iMin, iMax
260 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
261 & + PmEpR(i,j,bi,bj)
262 & *( temp_EvPrRn - theta(i,j,ks,bi,bj) )
263 & *mass2rUnit
264 ENDDO
265 ENDDO
266 ENDIF
267
268 IF (salt_EvPrRn.NE.UNSET_RL) THEN
269 DO j = jMin, jMax
270 DO i = iMin, iMax
271 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
272 & + PmEpR(i,j,bi,bj)
273 & *( salt_EvPrRn - salt(i,j,ks,bi,bj) )
274 & *mass2rUnit
275 ENDDO
276 ENDDO
277 ENDIF
278
279 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
280 ELSE
281 #else /* EXACT_CONSERV */
282 IF (.TRUE.) THEN
283 #endif /* EXACT_CONSERV */
284
285 C-- EmPmR does not really affect the water column height (for tracer budget)
286 C and is converted to a salt tendency.
287
288 IF (convertFW2Salt .EQ. -1.) THEN
289 C- use local surface tracer field to calculate forcing term:
290
291 IF (temp_EvPrRn.NE.UNSET_RL) THEN
292 C account for Rain/Evap heat content (temp_EvPrRn) using local SST
293 DO j = jMin, jMax
294 DO i = iMin, iMax
295 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
296 & + EmPmR(i,j,bi,bj)
297 & *( theta(i,j,ks,bi,bj) - temp_EvPrRn )
298 & *mass2rUnit
299 ENDDO
300 ENDDO
301 ENDIF
302 IF (salt_EvPrRn.NE.UNSET_RL) THEN
303 C converts EmPmR to salinity tendency using surface local salinity
304 DO j = jMin, jMax
305 DO i = iMin, iMax
306 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
307 & + EmPmR(i,j,bi,bj)
308 & *( salt(i,j,ks,bi,bj) - salt_EvPrRn )
309 & *mass2rUnit
310 ENDDO
311 ENDDO
312 ENDIF
313
314 ELSE
315 C- use uniform tracer value to calculate forcing term:
316
317 IF (temp_EvPrRn.NE.UNSET_RL) THEN
318 C account for Rain/Evap heat content (temp_EvPrRn) assuming uniform SST (=tRef)
319 DO j = jMin, jMax
320 DO i = iMin, iMax
321 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
322 & + EmPmR(i,j,bi,bj)
323 & *( tRef(ks) - temp_EvPrRn )
324 & *mass2rUnit
325 ENDDO
326 ENDDO
327 ENDIF
328 IF (salt_EvPrRn.NE.UNSET_RL) THEN
329 C converts EmPmR to virtual salt flux using uniform salinity (default=35)
330 DO j = jMin, jMax
331 DO i = iMin, iMax
332 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
333 & + EmPmR(i,j,bi,bj)
334 & *( convertFW2Salt - salt_EvPrRn )
335 & *mass2rUnit
336 ENDDO
337 ENDDO
338 ENDIF
339
340 C- end local-surface-tracer / uniform-value distinction
341 ENDIF
342
343 ENDIF
344
345 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
346
347 #ifdef ATMOSPHERIC_LOADING
348 C-- Atmospheric surface Pressure loading : added to phi0surf when using Z-coord;
349 C Not yet implemented for Ocean in P: would need to be applied to the other end
350 C of the column, as a vertical velocity (omega); (meaningless for Atmos in P).
351 C- Note:
352 C Using P-coord., a hack (now directly applied from S/R INI_FORCING)
353 C is sometime used to read phi0surf from a file (pLoadFile) instead
354 C of computing it from bathymetry & density ref. profile.
355
356 IF ( usingZCoords ) THEN
357 C The true atmospheric P-loading is not yet implemented for P-coord
358 C (requires time varying dP(Nr) like dP(k-bottom) with NonLin FS).
359 IF ( useRealFreshWaterFlux ) THEN
360 DO j = jMin, jMax
361 DO i = iMin, iMax
362 phi0surf(i,j,bi,bj) = ( pLoad(i,j,bi,bj)
363 & +sIceLoad(i,j,bi,bj)*gravity
364 & )*recip_rhoConst
365 ENDDO
366 ENDDO
367 ELSE
368 DO j = jMin, jMax
369 DO i = iMin, iMax
370 phi0surf(i,j,bi,bj) = pLoad(i,j,bi,bj)*recip_rhoConst
371 ENDDO
372 ENDDO
373 ENDIF
374 c ELSEIF ( usingPCoords ) THEN
375 C-- This is a hack used to read phi0surf from a file (pLoadFile)
376 C instead of computing it from bathymetry & density ref. profile.
377 C ==> now done only once, in S/R INI_FORCING
378 c DO j = jMin, jMax
379 c DO i = iMin, iMax
380 c phi0surf(i,j,bi,bj) = pLoad(i,j,bi,bj)
381 c ENDDO
382 c ENDDO
383 ENDIF
384 #endif /* ATMOSPHERIC_LOADING */
385
386 #ifdef ALLOW_SHELFICE
387 IF ( useSHELFICE) THEN
388 CALL SHELFICE_FORCING_SURF(
389 I bi, bj, iMin, iMax, jMin, jMax,
390 I myTime, myIter, myThid )
391 ENDIF
392 #endif /* ALLOW_SHELFICE */
393
394 C-- end bi,bj loops.
395 ENDDO
396 ENDDO
397
398 RETURN
399 END

  ViewVC Help
Powered by ViewVC 1.1.22