/[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.27 - (show annotations) (download)
Tue Sep 7 17:29:15 2004 UTC (19 years, 9 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint55, checkpoint54f_post, checkpoint55c_post, checkpoint55g_post, checkpoint55d_post, checkpoint55d_pre, checkpoint55b_post, checkpoint55f_post, checkpoint55a_post, checkpoint55e_post
Changes since 1.26: +2 -2 lines
 o remove single quotes (eg. "don't"-->"do not") so that the on-line code
   browser does not get confused

1 C $Header: /u/gcmpack/MITgcm/model/src/external_forcing_surf.F,v 1.26 2004/07/18 01:04:23 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
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 CEOP
55
56 IF ( buoyancyRelation .EQ. 'OCEANICP' ) THEN
57 ks = Nr
58 ELSE
59 ks = 1
60 ENDIF
61
62 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
63
64 IF ( doThetaClimRelax .OR. doSaltClimRelax ) THEN
65 C-- Start with surface restoring term :
66
67 DO j = jMin, jMax
68 DO i = iMin, iMax
69 #ifdef ALLOW_SEAICE
70 C Do not restore under sea-ice
71 C Heat Flux (restoring term) :
72 surfaceForcingT(i,j,bi,bj) =
73 & -lambdaThetaClimRelax * (1-AREA(i,j,1,bi,bj))
74 & *(theta(i,j,ks,bi,bj)-SST(i,j,bi,bj))
75 & *drF(ks)*hFacC(i,j,ks,bi,bj)
76 C Salt Flux (restoring term) :
77 surfaceForcingS(i,j,bi,bj) =
78 & -lambdaSaltClimRelax * (1-AREA(i,j,1,bi,bj))
79 & *(salt(i,j,ks,bi,bj)-SSS(i,j,bi,bj))
80 & *drF(ks)*hFacC(i,j,ks,bi,bj)
81 #else /* ifndef ALLOW_SEAICE */
82 C Heat Flux (restoring term) :
83 IF ( abs(yC(i,j,bi,bj)).LE.latBandClimRelax ) THEN
84 surfaceForcingT(i,j,bi,bj) =
85 & -lambdaThetaClimRelax
86 & *(theta(i,j,ks,bi,bj)-SST(i,j,bi,bj))
87 & *drF(ks)*hFacC(i,j,ks,bi,bj)
88 C Salt Flux (restoring term) :
89 surfaceForcingS(i,j,bi,bj) =
90 & -lambdaSaltClimRelax
91 & *(salt(i,j,ks,bi,bj)-SSS(i,j,bi,bj))
92 & *drF(ks)*hFacC(i,j,ks,bi,bj)
93 ELSE
94 surfaceForcingT(i,j,bi,bj) = 0. _d 0
95 surfaceForcingS(i,j,bi,bj) = 0. _d 0
96 ENDIF
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 DO j=jMin,jMax
108 DO i=iMin,iMax
109 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
110 & * rStarExpC(i,j,bi,bj)
111 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
112 & * rStarExpC(i,j,bi,bj)
113 ENDDO
114 ENDDO
115 ELSE
116 DO j=jMin,jMax
117 DO i=iMin,iMax
118 IF (ks.EQ.ksurfC(i,j,bi,bj)) THEN
119 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
120 & *recip_hFacC(i,j,ks,bi,bj)*hFac_surfC(i,j,bi,bj)
121 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
122 & *recip_hFacC(i,j,ks,bi,bj)*hFac_surfC(i,j,bi,bj)
123 ENDIF
124 ENDDO
125 ENDDO
126 ENDIF
127 ENDIF
128 #endif /* NONLIN_FRSURF */
129
130 ELSE
131 C-- No restoring for T & S : set surfaceForcingT,S to zero :
132
133 DO j = jMin, jMax
134 DO i = iMin, iMax
135 surfaceForcingT(i,j,bi,bj) = 0. _d 0
136 surfaceForcingS(i,j,bi,bj) = 0. _d 0
137 ENDDO
138 ENDDO
139
140 C-- end restoring / no restoring block.
141 ENDIF
142
143 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
144
145 C-- Surface Fluxes :
146
147 DO j = jMin, jMax
148 DO i = iMin, iMax
149
150 C Zonal wind stress fu:
151 surfaceForcingU(i,j,bi,bj) =
152 & fu(i,j,bi,bj)*horiVertRatio*recip_rhoConst
153 C Meridional wind stress fv:
154 surfaceForcingV(i,j,bi,bj) =
155 & fv(i,j,bi,bj)*horiVertRatio*recip_rhoConst
156 C Net heat flux Qnet:
157 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
158 & - ( Qnet(i,j,bi,bj)
159 #ifdef SHORTWAVE_HEATING
160 & -Qsw(i,j,bi,bj)
161 #endif
162 & ) *recip_Cp*horiVertRatio*recip_rhoConst
163 C Net Salt Flux :
164 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
165 & -saltFlux(i,j,bi,bj)*horiVertRatio*recip_rhoConst
166
167 ENDDO
168 ENDDO
169
170 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
171 C-- Fresh-water flux
172
173 #ifdef EXACT_CONSERV
174 c NB: synchronous time step: PmEpR lag 1 time step behind EmPmR
175 c to stay consitent with volume change (=d/dt etaH).
176 IF ( staggerTimeStep ) THEN
177 DO j=1,sNy
178 DO i=1,sNx
179 PmEpR(i,j,bi,bj) = -EmPmR(i,j,bi,bj)
180 ENDDO
181 ENDDO
182 ENDIF
183
184 IF ( (nonlinFreeSurf.GT.0 .OR. buoyancyRelation.EQ.'OCEANICP')
185 & .AND. useRealFreshWaterFlux ) THEN
186
187 c- NonLin_FrSurf and RealFreshWaterFlux : PmEpR effectively changes
188 c the water column height ; temp., salt, (tracer) flux associated
189 c with this input/output of water is added here to the surface tendency.
190 c
191
192 IF (temp_EvPrRn.NE.UNSET_RL) THEN
193 DO j = jMin, jMax
194 DO i = iMin, iMax
195 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
196 & + PmEpR(i,j,bi,bj)
197 & *( temp_EvPrRn - theta(i,j,ks,bi,bj) )
198 & *convertEmP2rUnit
199 ENDDO
200 ENDDO
201 ENDIF
202
203 IF (salt_EvPrRn.NE.UNSET_RL) THEN
204 DO j = jMin, jMax
205 DO i = iMin, iMax
206 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
207 & + PmEpR(i,j,bi,bj)
208 & *( salt_EvPrRn - salt(i,j,ks,bi,bj) )
209 & *convertEmP2rUnit
210 ENDDO
211 ENDDO
212 ENDIF
213
214 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
215 ELSE
216 #else /* EXACT_CONSERV */
217 IF (.TRUE.) THEN
218 #endif /* EXACT_CONSERV */
219
220 c- EmPmR does not really affect the water column height (for tracer budget)
221 c and is converted to a salt tendency.
222
223 IF (convertFW2Salt .EQ. -1.) THEN
224 c- converts EmPmR to salinity tendency using surface local salinity
225 DO j = jMin, jMax
226 DO i = iMin, iMax
227 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
228 & + EmPmR(i,j,bi,bj)*salt(i,j,ks,bi,bj)
229 & *convertEmP2rUnit
230 ENDDO
231 ENDDO
232 ELSE
233 c- converts EmPmR to virtual salt flux using uniform salinity (default=35)
234 DO j = jMin, jMax
235 DO i = iMin, iMax
236 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
237 & + EmPmR(i,j,bi,bj)*convertFW2Salt
238 & *convertEmP2rUnit
239 ENDDO
240 ENDDO
241 ENDIF
242
243 ENDIF
244
245 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
246
247 #ifdef ALLOW_PTRACERS
248 IF ( usePTRACERS ) THEN
249 CALL PTRACERS_FORCING_SURF(
250 I bi, bj, iMin, iMax, jMin, jMax,
251 I myTime,myIter,myThid )
252 ENDIF
253 #endif /* ALLOW_PTRACERS */
254
255 #ifdef ATMOSPHERIC_LOADING
256
257 C-- Atmospheric surface Pressure loading :
258
259 IF ( buoyancyRelation .EQ. 'OCEANIC' ) THEN
260 IF ( useRealFreshWaterFlux ) THEN
261 DO j = jMin, jMax
262 DO i = iMin, iMax
263 phi0surf(i,j,bi,bj) = ( pload(i,j,bi,bj)
264 & +sIceLoad(i,j,bi,bj)*gravity
265 & )*recip_rhoConst
266 ENDDO
267 ENDDO
268 ELSE
269 DO j = jMin, jMax
270 DO i = iMin, iMax
271 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)*recip_rhoConst
272 ENDDO
273 ENDDO
274 ENDIF
275 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
276 C-- This is a hack used to read phi0surf from a file (ploadFile)
277 C instead of computing it from bathymetry & density ref. profile.
278 C The true atmospheric P-loading is not yet implemented for P-coord
279 C (requires time varying dP(Nr) like dP(k-bottom) with NonLin FS).
280 DO j = jMin, jMax
281 DO i = iMin, iMax
282 phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)
283 ENDDO
284 ENDDO
285 ENDIF
286
287 #endif /* ATMOSPHERIC_LOADING */
288
289 #ifdef ALLOW_EBM
290 c-- Values for surfaceForcingT, surfaceForcingS
291 c are overwritten by those produced by EBM
292 cph AD recomputation problems if these IF useEBM are used
293 cph IF ( useEBM ) THEN
294 CALL EBM_FORCING_SURF(
295 I bi, bj, iMin, iMax, jMin, jMax,
296 I myTime,myIter,myThid )
297 cph ENDIF
298 #endif
299
300 #ifdef ALLOW_TIMEAVE
301 c IF ( taveFreq .NE. 0. _d 0 ) THEN
302 c CALL TIMEAVE_SURF_FLUX( bi, bj, myTime, myIter, myThid)
303 c ENDIF
304 #endif /* ALLOW_TIMEAVE */
305
306 RETURN
307 END

  ViewVC Help
Powered by ViewVC 1.1.22