/[MITgcm]/MITgcm/model/src/external_forcing_surf.F
ViewVC logotype

Annotation of /MITgcm/model/src/external_forcing_surf.F

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


Revision 1.26 - (hide annotations) (download)
Sun Jul 18 01:04:23 2004 UTC (19 years, 11 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint54d_post, checkpoint54e_post, checkpoint54c_post
Changes since 1.25: +100 -101 lines
replace surfaceTendency U,V,S,T,Tice by surfaceForcing U,V,S,T,Tice

1 jmc 1.26 C $Header: $
2 cnh 1.5 C $Name: $
3 heimbach 1.1
4 edhill 1.13 #include "PACKAGES_CONFIG.h"
5 heimbach 1.1 #include "CPP_OPTIONS.h"
6    
7 cnh 1.5 CBOP
8     C !ROUTINE: EXTERNAL_FORCING_SURF
9     C !INTERFACE:
10 heimbach 1.2 SUBROUTINE EXTERNAL_FORCING_SURF(
11 edhill 1.16 I bi, bj, iMin, iMax, jMin, jMax,
12 dimitri 1.12 I myTime, myIter, myThid )
13 cnh 1.5 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 heimbach 1.1 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 jmc 1.6 #include "SURFACE.h"
31 dimitri 1.18 #ifdef ALLOW_SEAICE
32     #include "SEAICE.h"
33     #endif /* ALLOW_SEAICE */
34 heimbach 1.1
35 cnh 1.5 C !INPUT/OUTPUT PARAMETERS:
36 heimbach 1.1 C === Routine arguments ===
37 jmc 1.22 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 cnh 1.5 C myThid :: Thread no. that called this routine.
42 dimitri 1.12 _RL myTime
43     INTEGER myIter
44 heimbach 1.1 INTEGER myThid
45 edhill 1.16 INTEGER bi,bj
46     INTEGER iMin, iMax
47     INTEGER jMin, jMax
48 heimbach 1.1
49 cnh 1.5 C !LOCAL VARIABLES:
50 heimbach 1.1 C === Local variables ===
51 edhill 1.16 INTEGER i,j
52 mlosch 1.7 C number of surface interface layer
53 jmc 1.22 INTEGER ks
54 cnh 1.5 CEOP
55 heimbach 1.2
56 jmc 1.26 IF ( buoyancyRelation .EQ. 'OCEANICP' ) THEN
57 jmc 1.22 ks = Nr
58 jmc 1.26 ELSE
59 jmc 1.22 ks = 1
60 jmc 1.26 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 Don't 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 mlosch 1.7
145 jmc 1.14 C-- Surface Fluxes :
146    
147 edhill 1.16 DO j = jMin, jMax
148     DO i = iMin, iMax
149 heimbach 1.1
150 jmc 1.26 C Zonal wind stress fu:
151     surfaceForcingU(i,j,bi,bj) =
152 mlosch 1.7 & fu(i,j,bi,bj)*horiVertRatio*recip_rhoConst
153 jmc 1.26 C Meridional wind stress fv:
154     surfaceForcingV(i,j,bi,bj) =
155 mlosch 1.7 & fv(i,j,bi,bj)*horiVertRatio*recip_rhoConst
156 jmc 1.26 C Net heat flux Qnet:
157     surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
158 jmc 1.24 & - ( Qnet(i,j,bi,bj)
159     #ifdef SHORTWAVE_HEATING
160 jmc 1.26 & -Qsw(i,j,bi,bj)
161 jmc 1.24 #endif
162     & ) *recip_Cp*horiVertRatio*recip_rhoConst
163 jmc 1.14 C Net Salt Flux :
164 jmc 1.26 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
165 jmc 1.14 & -saltFlux(i,j,bi,bj)*horiVertRatio*recip_rhoConst
166 edhill 1.16
167 heimbach 1.2 ENDDO
168 edhill 1.16 ENDDO
169 jmc 1.14
170 jmc 1.22 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
171     C-- Fresh-water flux
172 jmc 1.6
173 jmc 1.22 #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 edhill 1.16 ENDDO
182     ENDIF
183 jmc 1.14
184 edhill 1.16 IF ( (nonlinFreeSurf.GT.0 .OR. buoyancyRelation.EQ.'OCEANICP')
185     & .AND. useRealFreshWaterFlux ) THEN
186 jmc 1.6
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 edhill 1.16 IF (temp_EvPrRn.NE.UNSET_RL) THEN
193     DO j = jMin, jMax
194     DO i = iMin, iMax
195 jmc 1.26 surfaceForcingT(i,j,bi,bj) = surfaceForcingT(i,j,bi,bj)
196 edhill 1.16 & + PmEpR(i,j,bi,bj)
197 jmc 1.22 & *( temp_EvPrRn - theta(i,j,ks,bi,bj) )
198 edhill 1.16 & *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 jmc 1.26 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
207 edhill 1.16 & + PmEpR(i,j,bi,bj)
208 jmc 1.22 & *( salt_EvPrRn - salt(i,j,ks,bi,bj) )
209 edhill 1.16 & *convertEmP2rUnit
210     ENDDO
211     ENDDO
212     ENDIF
213 jmc 1.6
214 jmc 1.11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
215 edhill 1.16 ELSE
216 jmc 1.22 #else /* EXACT_CONSERV */
217 edhill 1.16 IF (.TRUE.) THEN
218 jmc 1.22 #endif /* EXACT_CONSERV */
219 jmc 1.11
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 edhill 1.16 IF (convertFW2Salt .EQ. -1.) THEN
224 jmc 1.11 c- converts EmPmR to salinity tendency using surface local salinity
225 edhill 1.16 DO j = jMin, jMax
226     DO i = iMin, iMax
227 jmc 1.26 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
228 jmc 1.22 & + EmPmR(i,j,bi,bj)*salt(i,j,ks,bi,bj)
229 edhill 1.16 & *convertEmP2rUnit
230     ENDDO
231     ENDDO
232     ELSE
233 jmc 1.11 c- converts EmPmR to virtual salt flux using uniform salinity (default=35)
234 edhill 1.16 DO j = jMin, jMax
235     DO i = iMin, iMax
236 jmc 1.26 surfaceForcingS(i,j,bi,bj) = surfaceForcingS(i,j,bi,bj)
237 edhill 1.16 & + EmPmR(i,j,bi,bj)*convertFW2Salt
238     & *convertEmP2rUnit
239     ENDDO
240     ENDDO
241     ENDIF
242 jmc 1.11
243 edhill 1.16 ENDIF
244 heimbach 1.20
245 jmc 1.11 C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
246 jmc 1.25
247 dimitri 1.12 #ifdef ALLOW_PTRACERS
248 edhill 1.16 IF ( usePTRACERS ) THEN
249     CALL PTRACERS_FORCING_SURF(
250 heimbach 1.20 I bi, bj, iMin, iMax, jMin, jMax,
251     I myTime,myIter,myThid )
252 edhill 1.16 ENDIF
253 dimitri 1.12 #endif /* ALLOW_PTRACERS */
254 jmc 1.11
255     #ifdef ATMOSPHERIC_LOADING
256    
257     C-- Atmospheric surface Pressure loading :
258    
259 jmc 1.23 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 edhill 1.16 DO j = jMin, jMax
270     DO i = iMin, iMax
271     phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)*recip_rhoConst
272 jmc 1.11 ENDDO
273 edhill 1.16 ENDDO
274 jmc 1.23 ENDIF
275 edhill 1.16 ELSEIF ( buoyancyRelation .eq. 'OCEANICP' ) THEN
276 jmc 1.11 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 edhill 1.16 DO j = jMin, jMax
281     DO i = iMin, iMax
282     phi0surf(i,j,bi,bj) = pload(i,j,bi,bj)
283 jmc 1.11 ENDDO
284 edhill 1.16 ENDDO
285     ENDIF
286 jmc 1.11
287     #endif /* ATMOSPHERIC_LOADING */
288 heimbach 1.20
289     #ifdef ALLOW_EBM
290 jmc 1.26 c-- Values for surfaceForcingT, surfaceForcingS
291 heimbach 1.20 c are overwritten by those produced by EBM
292 heimbach 1.21 cph AD recomputation problems if these IF useEBM are used
293     cph IF ( useEBM ) THEN
294 heimbach 1.20 CALL EBM_FORCING_SURF(
295     I bi, bj, iMin, iMax, jMin, jMax,
296     I myTime,myIter,myThid )
297 heimbach 1.21 cph ENDIF
298 heimbach 1.20 #endif
299 jmc 1.17
300     #ifdef ALLOW_TIMEAVE
301 jmc 1.22 c IF ( taveFreq .NE. 0. _d 0 ) THEN
302     c CALL TIMEAVE_SURF_FLUX( bi, bj, myTime, myIter, myThid)
303     c ENDIF
304 jmc 1.17 #endif /* ALLOW_TIMEAVE */
305 heimbach 1.1
306     RETURN
307     END

  ViewVC Help
Powered by ViewVC 1.1.22