/[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.31 - (show annotations) (download)
Mon Jul 11 19:30:42 2005 UTC (18 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint57m_post, checkpoint57s_post, checkpoint57r_post, checkpoint57n_post, checkpoint57l_post, checkpoint57t_post, checkpoint57v_post, checkpoint57y_pre, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint57o_post, checkpoint57w_post, checkpoint57x_post
Changes since 1.30: +20 -28 lines
call diagnostics_scale_fill (instead of diagnostics_fill) and avoid temp array

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

  ViewVC Help
Powered by ViewVC 1.1.22