/[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.33 - (show annotations) (download)
Fri Feb 10 10:00:24 2006 UTC (18 years, 4 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint58a_post
Changes since 1.32: +17 -2 lines
  - separate shelfice load anomaly from pload (breaks with time
    dependent forcing), => introduce constant field shelficeLoadAnomaly.
    Its default is 0., but it may be computed more cleverly from (unknown)
    t- and s-profiles (tRef, sRef) and actual EOS. For now this has to be
    done offline. A good approximation of the pressure load anomaly is
    necessary to avoid large initial adjustment processes underneath
    deep-reaching shelfice.

1 C $Header: /u/gcmpack/MITgcm/model/src/external_forcing_surf.F,v 1.32 2005/12/08 15:44:33 heimbach 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 #ifdef EXACT_CONSERV
194 c NB: synchronous time step: PmEpR lag 1 time step behind EmPmR
195 c to stay consitent with volume change (=d/dt etaH).
196 IF ( staggerTimeStep ) THEN
197 DO j=1,sNy
198 DO i=1,sNx
199 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
200 ENDDO
201 ENDDO
202 ENDIF
203
204 IF ( (nonlinFreeSurf.GT.0 .OR. usingPCoords)
205 & .AND. useRealFreshWaterFlux ) THEN
206
207 c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
208 c the water column height ; temp., salt, (tracer) flux associated
209 c with this input/output of water is added here to the surface tendency.
210 c
211
212 IF (temp_EvPrRn.NE.UNSET_RL) THEN
213 DO j = jMin, jMax
214 DO i = iMin, iMax
215 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
216 & + PmEpR(i,j,bi,bj)
217 & *( temp_EvPrRn - theta(i,j,ks,bi,bj) )
218 & *convertEmP2rUnit
219 ENDDO
220 ENDDO
221 ENDIF
222
223 IF (salt_EvPrRn.NE.UNSET_RL) THEN
224 DO j = jMin, jMax
225 DO i = iMin, iMax
226 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
227 & + PmEpR(i,j,bi,bj)
228 & *( salt_EvPrRn - salt(i,j,ks,bi,bj) )
229 & *convertEmP2rUnit
230 ENDDO
231 ENDDO
232 ENDIF
233
234 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
235 ELSE
236 #else /* EXACT_CONSERV */
237 IF (.TRUE.) THEN
238 #endif /* EXACT_CONSERV */
239
240 c- EmPmR does not really affect the water column height (for tracer budget)
241 c and is converted to a salt tendency.
242
243 IF (convertFW2Salt .EQ. -1.) THEN
244 c- converts EmPmR to salinity tendency using surface local salinity
245 DO j = jMin, jMax
246 DO i = iMin, iMax
247 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
248 & + EmPmR(i,j,bi,bj)*salt(i,j,ks,bi,bj)
249 & *convertEmP2rUnit
250 ENDDO
251 ENDDO
252 ELSE
253 c- converts EmPmR to virtual salt flux using uniform salinity (default=35)
254 DO j = jMin, jMax
255 DO i = iMin, iMax
256 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
257 & + EmPmR(i,j,bi,bj)*convertFW2Salt
258 & *convertEmP2rUnit
259 ENDDO
260 ENDDO
261 ENDIF
262
263 ENDIF
264
265 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
266
267 #ifdef ALLOW_PTRACERS
268 IF ( usePTRACERS ) THEN
269 CALL PTRACERS_FORCING_SURF(
270 I bi, bj, iMin, iMax, jMin, jMax,
271 I myTime,myIter,myThid )
272 ENDIF
273 #endif /* ALLOW_PTRACERS */
274
275 #ifdef ATMOSPHERIC_LOADING
276
277 C-- Atmospheric surface Pressure loading :
278
279 IF ( usingZCoords ) THEN
280 IF ( useRealFreshWaterFlux ) THEN
281 DO j = jMin, jMax
282 DO i = iMin, iMax
283 phi0surf(i,j,bi,bj) = ( pload(i,j,bi,bj)
284 & +sIceLoad(i,j,bi,bj)*gravity
285 & )*recip_rhoConst
286 ENDDO
287 ENDDO
288 ELSE
289 DO j = jMin, jMax
290 DO i = iMin, iMax
291 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)*recip_rhoConst
292 ENDDO
293 ENDDO
294 ENDIF
295 ELSEIF ( usingPCoords ) THEN
296 C-- This is a hack used to read phi0surf from a file (ploadFile)
297 C instead of computing it from bathymetry & density ref. profile.
298 C The true atmospheric P-loading is not yet implemented for P-coord
299 C (requires time varying dP(Nr) like dP(k-bottom) with NonLin FS).
300 DO j = jMin, jMax
301 DO i = iMin, iMax
302 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)
303 ENDDO
304 ENDDO
305 ENDIF
306
307 #endif /* ATMOSPHERIC_LOADING */
308
309 #ifdef ALLOW_SHELFICE
310 IF ( usingZCoords ) THEN
311 IF ( useSHELFICE) THEN
312 DO j = jMin, jMax
313 DO i = iMin, iMax
314 phi0surf(i,j,bi,bj) = phi0surf(i,j,bi,bj)
315 & + shelficeLoadAnomaly(i,j,bi,bj)*recip_rhoConst
316 ENDDO
317 ENDDO
318 ENDIF
319 ENDIF
320 #endif /* ALLOW_SHELFICE */
321
322 #ifdef ALLOW_EBM
323 c-- Values for surfaceForcingT, surfaceForcingS
324 c are overwritten by those produced by EBM
325 cph AD recomputation problems if these IF useEBM are used
326 cph IF ( useEBM ) THEN
327 CALL EBM_FORCING_SURF(
328 I bi, bj, iMin, iMax, jMin, jMax,
329 I myTime,myIter,myThid )
330 cph ENDIF
331 #endif
332
333 RETURN
334 END

  ViewVC Help
Powered by ViewVC 1.1.22