/[MITgcm]/MITgcm/pkg/seaice/seaice_get_forcing.F
ViewVC logotype

Contents of /MITgcm/pkg/seaice/seaice_get_forcing.F

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


Revision 1.8 - (show annotations) (download)
Mon Dec 27 20:34:11 2004 UTC (19 years, 4 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint58l_post, checkpoint57m_post, checkpoint58e_post, checkpoint57v_post, checkpoint57f_post, checkpoint57s_post, checkpoint57j_post, checkpoint58b_post, checkpoint58m_post, checkpoint57f_pre, checkpoint57k_post, checkpoint57d_post, checkpoint57g_post, checkpoint58r_post, checkpoint57h_pre, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint58n_post, checkpoint58x_post, checkpoint57g_pre, checkpoint58h_post, checkpoint57e_post, checkpoint58w_post, checkpoint58j_post, checkpoint57h_post, checkpoint57y_pre, checkpoint57c_pre, checkpoint57o_post, checkpoint57r_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint57i_post, checkpoint59b, checkpoint59i, checkpoint59h, checkpoint59k, checkpoint59j, checkpoint59, checkpoint58, checkpoint57h_done, checkpoint58f_post, checkpoint59c, checkpoint57n_post, checkpoint58d_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58o_post, checkpoint57z_post, eckpoint57e_pre, checkpoint58c_post, checkpoint58k_post, checkpoint57c_post, checkpoint58u_post, checkpoint58y_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint58t_post, checkpoint58q_post, checkpoint57l_post
Changes since 1.7: +1 -5 lines
o added seaice_summary.F and removed obsolete ALLOW_SEAICE's from pkg/seaice

1 C $Header: /u/gcmpack/MITgcm/pkg/seaice/seaice_get_forcing.F,v 1.7 2003/12/14 04:56:18 dimitri Exp $
2 C $Name: $
3
4 #include "SEAICE_OPTIONS.h"
5
6 CStartOfInterface
7 SUBROUTINE SEAICE_GET_FORCING( myTime, myIter, myThid )
8 C /==========================================================\
9 C | SUBROUTINE SEAICE_GET_FORCING |
10 C | o Load atmospheric state and runoff. |
11 C |==========================================================|
12 C \==========================================================/
13 IMPLICIT NONE
14
15 C === Global variables ===
16 #include "SIZE.h"
17 #include "EEPARAMS.h"
18 #include "PARAMS.h"
19 #include "FFIELDS.h"
20 #include "SEAICE_PARAMS.h"
21 #include "SEAICE_FFIELDS.h"
22
23 C === Routine arguments ===
24 C myTime - Simulation time
25 C myIter - Simulation timestep number
26 C myThid - Thread no. that called this routine.
27 _RL myTime
28 INTEGER myIter
29 INTEGER myThid
30 CEndOfInterface
31
32 INTEGER ILNBLNK
33 EXTERNAL ILNBLNK
34
35 #ifndef SEAICE_EXTERNAL_FORCING
36
37 C === Local arrays ===
38 COMMON /TDFIELDS_FLAGS/
39 & wind0_is_first, flux0_is_first,
40 & SSS0_is_first, SST0_is_first
41 LOGICAL wind0_is_first, flux0_is_first,
42 & SSS0_is_first, SST0_is_first
43
44 C === Local variables ===
45 CHARACTER*(MAX_LEN_MBUF) msgBuf
46 INTEGER bi,bj,i,j,iRec,iEnd
47 _RL aWghtWind,bWghtWind,aWghtFlux,bWghtFlux,
48 & aWghtSSS,bWghtSSS,aWghtSST,bWghtSST
49 _RS initValue
50 _RL year, seconds, YearTime, four
51 INTEGER CurrentYear, CurrentYear2
52 logical done
53 CHARACTER*(MAX_LEN_MBUF) fName
54
55 C-- Compute CurrentYear and YearTime
56 four = 4.0
57 YearTime = myTime
58 done = .false.
59 do year = StartingYear, EndingYear
60 if( .not. done ) then
61 if( mod(year,four) .eq. 0. ) then
62 seconds = 366.*24.*60.*60.
63 else
64 seconds = 365.*24.*60.*60.
65 endif
66 if( YearTime-seconds .ge. 0. ) then
67 YearTime = YearTime-seconds
68 else
69 CurrentYear = year
70 done = .true.
71 endif
72 endif
73 enddo
74 if( CurrentYear.ge.2000 ) then
75 CurrentYear2 = CurrentYear-2000
76 else
77 CurrentYear2 = CurrentYear-1900
78 endif
79
80 C-- Check to see whether myTime is outside available forcing data
81 IF( CurrentYear.gt. EndingYear .or.
82 & YearTime .lt. WindForcingStart .or.
83 & YearTime .gt. WindForcingEnd .or.
84 & YearTime .lt. FluxForcingStart .or.
85 & YearTime .gt. FluxForcingEnd .or.
86 & YearTime .lt. SSTforcingStart .or.
87 & YearTime .gt. SSTforcingEnd .or.
88 & YearTime .lt. SSSforcingStart .or.
89 & YearTime .gt. SSSforcingEnd ) THEN
90 WRITE(msgBuf,'(A)') 'No Available Forcing Data'
91 CALL PRINT_ERROR( msgBuf , 1)
92 STOP 'ABNORMAL END: S/R SEAICE_GET_FORCING'
93 ENDIF
94
95 C-- First call requires that we initialize everything for safety
96 IF ( myIter .EQ. nIter0 ) THEN
97 initValue = ZERO
98 CALL INIT_ARRAY_RS( uwind0 , initValue, myThid )
99 CALL INIT_ARRAY_RS( uwind1 , initValue, myThid )
100 CALL INIT_ARRAY_RS( vwind0 , initValue, myThid )
101 CALL INIT_ARRAY_RS( vwind1 , initValue, myThid )
102 initValue = 283. _d 0
103 CALL INIT_ARRAY_RS( atemp0 , initValue, myThid )
104 CALL INIT_ARRAY_RS( atemp1 , initValue, myThid )
105 initValue = 0.005 _d 0
106 CALL INIT_ARRAY_RS( aqh0 , initValue, myThid )
107 CALL INIT_ARRAY_RS( aqh1 , initValue, myThid )
108 initValue = 300. _d 0
109 CALL INIT_ARRAY_RS( lwdown0 , initValue, myThid )
110 CALL INIT_ARRAY_RS( lwdown1 , initValue, myThid )
111 initValue = 200. _d 0
112 CALL INIT_ARRAY_RS( swdown0 , initValue, myThid )
113 CALL INIT_ARRAY_RS( swdown1 , initValue, myThid )
114 initValue = ZERO
115 CALL INIT_ARRAY_RS( precip0 , initValue, myThid )
116 CALL INIT_ARRAY_RS( precip1 , initValue, myThid )
117 CALL INIT_ARRAY_RS( evap0 , initValue, myThid )
118 CALL INIT_ARRAY_RS( evap1 , initValue, myThid )
119 CALL INIT_ARRAY_RS( runoff0 , initValue, myThid )
120 CALL INIT_ARRAY_RS( runoff1 , initValue, myThid )
121 initValue = 35. _d 0
122 CALL INIT_ARRAY_RS( SSSsi0 , initValue, myThid )
123 CALL INIT_ARRAY_RS( SSSsi1 , initValue, myThid )
124 initValue = 10. _d 0
125 CALL INIT_ARRAY_RS( SSTsi0 , initValue, myThid )
126 CALL INIT_ARRAY_RS( SSTsi1 , initValue, myThid )
127
128 wind0_is_first = .TRUE.
129 flux0_is_first = .TRUE.
130 SSS0_is_first = .TRUE.
131 SST0_is_first = .TRUE.
132
133 _BEGIN_MASTER(myThid)
134 write(0,*)
135 & 'S/R SEAICE_GET_FORCING: initialize',myTime,myIter
136
137 iRec = int((YearTime-WindForcingStart)/WindForcingPeriod) + 1
138 IF ( uwindFile .NE. ' ' ) THEN
139 iEnd = ILNBLNK( uwindFile ) - 2
140 WRITE(fName,'(A,I2.2)') uwindFile(1:iEnd), CurrentYear2
141 CALL READ_REC_XY_RS( fName,uwind0,iRec ,myIter,myThid )
142 CALL READ_REC_XY_RS( fName,uwind1,iRec+1,myIter,myThid )
143 ENDIF
144 IF ( vwindFile .NE. ' ' ) THEN
145 iEnd = ILNBLNK( vwindFile ) - 2
146 WRITE(fName,'(A,I2.2)') vwindFile(1:iEnd), CurrentYear2
147 CALL READ_REC_XY_RS( fName,vwind0,iRec ,myIter,myThid )
148 CALL READ_REC_XY_RS( fName,vwind1,iRec+1,myIter,myThid )
149 ENDIF
150
151 iRec = int((YearTime-FluxForcingStart)/FluxForcingPeriod) + 1
152 IF ( atempFile .NE. ' ' ) THEN
153 iEnd = ILNBLNK( atempFile ) - 4
154 WRITE(fName,'(A,I4.4)') atempFile(1:iEnd), CurrentYear
155 CALL READ_REC_XY_RS( fName,atemp0,iRec ,myIter,myThid )
156 CALL READ_REC_XY_RS( fName,atemp1,iRec+1,myIter,myThid )
157 ENDIF
158 IF ( aqhFile .NE. ' ' ) THEN
159 iEnd = ILNBLNK( aqhFile ) - 4
160 WRITE(fName,'(A,I4.4)') aqhFile(1:iEnd), CurrentYear
161 CALL READ_REC_XY_RS( fName,aqh0,iRec ,myIter,myThid )
162 CALL READ_REC_XY_RS( fName,aqh1,iRec+1,myIter,myThid )
163 ENDIF
164 IF ( lwdownFile .NE. ' ' ) THEN
165 iEnd = ILNBLNK( lwdownFile ) - 4
166 WRITE(fName,'(A,I4.4)') lwdownFile(1:iEnd), CurrentYear
167 CALL READ_REC_XY_RS( fName,lwdown0,iRec ,myIter,myThid )
168 CALL READ_REC_XY_RS( fName,lwdown1,iRec+1,myIter,myThid )
169 ENDIF
170 IF ( swdownFile .NE. ' ' ) THEN
171 iEnd = ILNBLNK( swdownFile ) - 4
172 WRITE(fName,'(A,I4.4)') swdownFile(1:iEnd), CurrentYear
173 CALL READ_REC_XY_RS( fName,swdown0,iRec ,myIter,myThid )
174 CALL READ_REC_XY_RS( fName,swdown1,iRec+1,myIter,myThid )
175 ENDIF
176 IF ( precipFile .NE. ' ' ) THEN
177 iEnd = ILNBLNK( precipFile ) - 4
178 WRITE(fName,'(A,I4.4)') precipFile(1:iEnd), CurrentYear
179 CALL READ_REC_XY_RS( fName,precip0,iRec ,myIter,myThid )
180 CALL READ_REC_XY_RS( fName,precip1,iRec+1,myIter,myThid )
181 ENDIF
182 IF ( evapFile .NE. ' ' ) THEN
183 iEnd = ILNBLNK( evapFile ) - 4
184 WRITE(fName,'(A,I4.4)') evapFile(1:iEnd), CurrentYear
185 CALL READ_REC_XY_RS( fName,evap0,iRec ,myIter,myThid )
186 CALL READ_REC_XY_RS( fName,evap1,iRec+1,myIter,myThid )
187 ENDIF
188 IF ( runoffFile .NE. ' ' ) THEN
189 iEnd = ILNBLNK( runoffFile ) - 4
190 WRITE(fName,'(A,I4.4)') runoffFile(1:iEnd), CurrentYear
191 CALL READ_REC_XY_RS( fName,runoff0,iRec ,myIter,myThid )
192 CALL READ_REC_XY_RS( fName,runoff1,iRec+1,myIter,myThid )
193 ENDIF
194
195 iRec = int((YearTime-SSTforcingStart)/SSTforcingPeriod) + 1
196 IF ( thetaClimFile .NE. ' ' ) THEN
197 iEnd = ILNBLNK( thetaClimFile ) - 2
198 WRITE(fName,'(A,I2.2)') thetaClimFile(1:iEnd), CurrentYear2
199 CALL READ_REC_XY_RS( fName,SSTsi0,iRec ,myIter,myThid )
200 CALL READ_REC_XY_RS( fName,SSTsi1,iRec+1,myIter,myThid )
201 ENDIF
202
203 iRec = int((YearTime-SSSforcingStart)/SSSforcingPeriod) + 1
204 IF ( saltClimFile .NE. ' ' ) THEN
205 CALL READ_REC_XY_RS( saltClimFile,SSSsi0,iRec ,myIter,myThid )
206 CALL READ_REC_XY_RS( saltClimFile,SSSsi1,iRec+1,myIter,myThid )
207 ENDIF
208
209 _END_MASTER(myThid)
210
211 CALL EXCH_UV_XY_RS(uwind0, vwind0, .TRUE., myThid)
212 CALL EXCH_UV_XY_RS(uwind1, vwind1, .TRUE., myThid)
213 _EXCH_XY_R4( atemp0, myThid )
214 _EXCH_XY_R4( atemp1, myThid )
215 _EXCH_XY_R4( aqh0, myThid )
216 _EXCH_XY_R4( aqh1, myThid )
217 _EXCH_XY_R4( lwdown0, myThid )
218 _EXCH_XY_R4( lwdown1, myThid )
219 _EXCH_XY_R4( swdown0, myThid )
220 _EXCH_XY_R4( swdown1, myThid )
221 _EXCH_XY_R4( precip0, myThid )
222 _EXCH_XY_R4( precip1, myThid )
223 _EXCH_XY_R4( evap0, myThid )
224 _EXCH_XY_R4( evap1, myThid )
225 _EXCH_XY_R4( runoff0, myThid )
226 _EXCH_XY_R4( runoff1, myThid )
227 _EXCH_XY_R4( SSTsi0, myThid )
228 _EXCH_XY_R4( SSTsi1, myThid )
229 _EXCH_XY_R4( SSSsi0, myThid )
230 _EXCH_XY_R4( SSSsi1, myThid )
231
232 ENDIF
233
234 C-- Now calculate whether if it is time to update wind speed arrays
235 iRec = int((YearTime-WindForcingStart)/WindForcingPeriod) + 2
236 aWghtWind = mod(YearTime-WindForcingStart,WindForcingPeriod) /
237 & WindForcingPeriod
238 bWghtWind=ONE-aWghtWind
239 IF ( aWghtWind .EQ. 0 ) THEN
240 _BEGIN_MASTER(myThid)
241 write(0,*)
242 & 'S/R SEAICE_GET_FORCING: reading winds',myTime,myIter
243 IF ( uwindFile .NE. ' ' ) THEN
244 iEnd = ILNBLNK( uwindFile ) - 2
245 WRITE(fName,'(A,I2.2)') uwindFile(1:iEnd), CurrentYear2
246 IF (wind0_is_first) THEN
247 CALL READ_REC_XY_RS( fName,uwind0,iRec,myIter,myThid )
248 ELSE
249 CALL READ_REC_XY_RS( fName,uwind1,iRec,myIter,myThid )
250 ENDIF
251 ENDIF
252 IF ( vwindFile .NE. ' ' ) THEN
253 iEnd = ILNBLNK( vwindFile ) - 2
254 WRITE(fName,'(A,I2.2)') vwindFile(1:iEnd), CurrentYear2
255 IF (wind0_is_first) THEN
256 CALL READ_REC_XY_RS( fName,vwind0,iRec,myIter,myThid )
257 ELSE
258 CALL READ_REC_XY_RS( fName,vwind1,iRec,myIter,myThid )
259 ENDIF
260 ENDIF
261 _END_MASTER(myThid)
262 IF (wind0_is_first) THEN
263 CALL EXCH_UV_XY_RS(uwind0, vwind0, .TRUE., myThid)
264 wind0_is_first=.FALSE.
265 ELSE
266 CALL EXCH_UV_XY_RS(uwind1, vwind1, .TRUE., myThid)
267 wind0_is_first=.TRUE.
268 ENDIF
269 ENDIF
270
271 C-- Now calculate whether if it is time to update heat and freshwater flux
272 iRec = int((YearTime-FluxForcingStart)/FluxForcingPeriod) + 2
273 aWghtFlux = mod(YearTime-FluxForcingStart,FluxForcingPeriod) /
274 & FluxForcingPeriod
275 bWghtFlux=ONE-aWghtFlux
276 IF ( aWghtFlux .EQ. 0 ) THEN
277 _BEGIN_MASTER(myThid)
278 write(0,*)
279 & 'S/R SEAICE_GET_FORCING: reading fluxes',myTime,myIter
280 IF ( atempFile .NE. ' ' ) THEN
281 iEnd = ILNBLNK( atempFile ) - 4
282 WRITE(fName,'(A,I4.4)') atempFile(1:iEnd), CurrentYear
283 IF (flux0_is_first) THEN
284 CALL READ_REC_XY_RS( fName,atemp0,iRec,myIter,myThid )
285 ELSE
286 CALL READ_REC_XY_RS( fName,atemp1,iRec,myIter,myThid )
287 ENDIF
288 ENDIF
289 IF ( aqhFile .NE. ' ' ) THEN
290 iEnd = ILNBLNK( aqhFile ) - 4
291 WRITE(fName,'(A,I4.4)') aqhFile(1:iEnd), CurrentYear
292 IF (flux0_is_first) THEN
293 CALL READ_REC_XY_RS( fName,aqh0,iRec,myIter,myThid )
294 ELSE
295 CALL READ_REC_XY_RS( fName,aqh1,iRec,myIter,myThid )
296 ENDIF
297 ENDIF
298 IF ( lwdownFile .NE. ' ' ) THEN
299 iEnd = ILNBLNK( lwdownFile ) - 4
300 WRITE(fName,'(A,I4.4)') lwdownFile(1:iEnd), CurrentYear
301 IF (flux0_is_first) THEN
302 CALL READ_REC_XY_RS( fName,lwdown0,iRec,myIter,myThid )
303 ELSE
304 CALL READ_REC_XY_RS( fName,lwdown1,iRec,myIter,myThid )
305 ENDIF
306 ENDIF
307 IF ( swdownFile .NE. ' ' ) THEN
308 iEnd = ILNBLNK( swdownFile ) - 4
309 WRITE(fName,'(A,I4.4)') swdownFile(1:iEnd), CurrentYear
310 IF (flux0_is_first) THEN
311 CALL READ_REC_XY_RS( fName,swdown0,iRec,myIter,myThid )
312 ELSE
313 CALL READ_REC_XY_RS( fName,swdown1,iRec,myIter,myThid )
314 ENDIF
315 ENDIF
316 IF ( precipFile .NE. ' ' ) THEN
317 iEnd = ILNBLNK( precipFile ) - 4
318 WRITE(fName,'(A,I4.4)') precipFile(1:iEnd), CurrentYear
319 IF (flux0_is_first) THEN
320 CALL READ_REC_XY_RS( fName,precip0,iRec,myIter,myThid )
321 ELSE
322 CALL READ_REC_XY_RS( fName,precip1,iRec,myIter,myThid )
323 ENDIF
324 ENDIF
325 IF ( evapFile .NE. ' ' ) THEN
326 iEnd = ILNBLNK( evapFile ) - 4
327 WRITE(fName,'(A,I4.4)') evapFile(1:iEnd), CurrentYear
328 IF (flux0_is_first) THEN
329 CALL READ_REC_XY_RS( fName,evap0,iRec,myIter,myThid )
330 ELSE
331 CALL READ_REC_XY_RS( fName,evap1,iRec,myIter,myThid )
332 ENDIF
333 ENDIF
334 IF ( runoffFile .NE. ' ' ) THEN
335 iEnd = ILNBLNK( runoffFile ) - 4
336 WRITE(fName,'(A,I4.4)') runoffFile(1:iEnd), CurrentYear
337 IF (flux0_is_first) THEN
338 CALL READ_REC_XY_RS( fName,runoff0,iRec,myIter,myThid )
339 ELSE
340 CALL READ_REC_XY_RS( fName,runoff1,iRec,myIter,myThid )
341 ENDIF
342 ENDIF
343 _END_MASTER(myThid)
344 IF (flux0_is_first) THEN
345 _EXCH_XY_R4(atemp0, myThid )
346 _EXCH_XY_R4(aqh0, myThid )
347 _EXCH_XY_R4(lwdown0, myThid )
348 _EXCH_XY_R4(swdown0, myThid )
349 _EXCH_XY_R4(precip0, myThid )
350 _EXCH_XY_R4(evap0, myThid )
351 _EXCH_XY_R4(runoff0, myThid )
352 flux0_is_first=.FALSE.
353 ELSE
354 _EXCH_XY_R4(atemp1, myThid )
355 _EXCH_XY_R4(aqh1, myThid )
356 _EXCH_XY_R4(lwdown1, myThid )
357 _EXCH_XY_R4(swdown1, myThid )
358 _EXCH_XY_R4(precip1, myThid )
359 _EXCH_XY_R4(evap1, myThid )
360 _EXCH_XY_R4(runoff1, myThid )
361 flux0_is_first=.TRUE.
362 ENDIF
363 ENDIF
364
365 C-- Now calculate whether if it is time to update SST array
366 iRec = int((YearTime-SSTforcingStart)/SSTforcingPeriod) + 2
367 aWghtSST = mod(YearTime-SSTforcingStart,SSTforcingPeriod) /
368 & SSTforcingPeriod
369 bWghtSST=ONE-aWghtSST
370 IF ( aWghtSST .EQ. 0 .AND. thetaClimFile .NE. ' ' ) THEN
371 _BEGIN_MASTER(myThid)
372 write(0,*) 'S/R SEAICE_GET_FORCING: reading SST',myTime,myIter
373 iEnd = ILNBLNK( thetaClimFile ) - 2
374 WRITE(fName,'(A,I2.2)') thetaClimFile(1:iEnd), CurrentYear2
375 IF (SST0_is_first) THEN
376 CALL READ_REC_XY_RS( fName,SSTsi0,iRec,myIter,myThid )
377 ELSE
378 CALL READ_REC_XY_RS( fName,SSTsi1,iRec,myIter,myThid )
379 ENDIF
380 _END_MASTER(myThid)
381 IF (SST0_is_first) THEN
382 _EXCH_XY_R4( SSTsi0, myThid )
383 SST0_is_first=.FALSE.
384 ELSE
385 _EXCH_XY_R4( SSTsi1, myThid )
386 SST0_is_first=.TRUE.
387 ENDIF
388 ENDIF
389
390 C-- Now calculate whether if it is time to update SSS array
391 iRec = int((YearTime-SSSforcingStart)/SSSforcingPeriod) + 2
392 aWghtSSS = mod(YearTime-SSSforcingStart,SSSforcingPeriod) /
393 & SSSforcingPeriod
394 bWghtSSS=ONE-aWghtSSS
395 IF ( aWghtSSS .EQ. 0 .AND. saltClimFile .NE. ' ') THEN
396 _BEGIN_MASTER(myThid)
397 write(0,*) 'S/R SEAICE_GET_FORCING: reading SSS',myTime,myIter
398 IF (SSS0_is_first) THEN
399 CALL READ_REC_XY_RS( saltClimFile,SSSsi0,iRec,myIter,myThid )
400 ELSE
401 CALL READ_REC_XY_RS( saltClimFile,SSSsi1,iRec,myIter,myThid )
402 ENDIF
403 _END_MASTER(myThid)
404 IF (SSS0_is_first) THEN
405 _EXCH_XY_R4( SSSsi0, myThid )
406 SSS0_is_first=.FALSE.
407 ELSE
408 _EXCH_XY_R4( SSSsi1, myThid )
409 SSS0_is_first=.TRUE.
410 ENDIF
411 ENDIF
412
413 C-- Time interpolation of wind forcing variables.
414 IF (wind0_is_first) THEN
415 DO bj = myByLo(myThid), myByHi(myThid)
416 DO bi = myBxLo(myThid), myBxHi(myThid)
417 DO j=1-Oly,sNy+Oly
418 DO i=1-Olx,sNx+Olx
419 uwind(i,j,bi,bj) = bWghtWind * uwind0(i,j,bi,bj) +
420 & aWghtWind * uwind1(i,j,bi,bj)
421 vwind(i,j,bi,bj) = bWghtWind * vwind0(i,j,bi,bj) +
422 & aWghtWind * vwind1(i,j,bi,bj)
423 ENDDO
424 ENDDO
425 ENDDO
426 ENDDO
427 ELSE
428 DO bj = myByLo(myThid), myByHi(myThid)
429 DO bi = myBxLo(myThid), myBxHi(myThid)
430 DO j=1-Oly,sNy+Oly
431 DO i=1-Olx,sNx+Olx
432 uwind(i,j,bi,bj) = aWghtWind * uwind0(i,j,bi,bj) +
433 & bWghtWind * uwind1(i,j,bi,bj)
434 vwind(i,j,bi,bj) = aWghtWind * vwind0(i,j,bi,bj) +
435 & bWghtWind * vwind1(i,j,bi,bj)
436 ENDDO
437 ENDDO
438 ENDDO
439 ENDDO
440 ENDIF
441
442 C-- Time interpolation of flux forcing variables.
443 IF (flux0_is_first) THEN
444 DO bj = myByLo(myThid), myByHi(myThid)
445 DO bi = myBxLo(myThid), myBxHi(myThid)
446 DO j=1-Oly,sNy+Oly
447 DO i=1-Olx,sNx+Olx
448 atemp(i,j,bi,bj) = bWghtFlux * atemp0(i,j,bi,bj) +
449 & aWghtFlux * atemp1(i,j,bi,bj)
450 aqh(i,j,bi,bj) = bWghtFlux * aqh0(i,j,bi,bj) +
451 & aWghtFlux * aqh1(i,j,bi,bj)
452 lwdown(i,j,bi,bj) = bWghtFlux * lwdown0(i,j,bi,bj) +
453 & aWghtFlux * lwdown1(i,j,bi,bj)
454 swdown(i,j,bi,bj) = bWghtFlux * swdown0(i,j,bi,bj) +
455 & aWghtFlux * swdown1(i,j,bi,bj)
456 precip(i,j,bi,bj) = bWghtFlux * precip0(i,j,bi,bj) +
457 & aWghtFlux * precip1(i,j,bi,bj)
458 evap(i,j,bi,bj) = bWghtFlux * evap0(i,j,bi,bj) +
459 & aWghtFlux * evap1(i,j,bi,bj)
460 runoff(i,j,bi,bj) = bWghtFlux * runoff0(i,j,bi,bj) +
461 & aWghtFlux * runoff1(i,j,bi,bj)
462 ENDDO
463 ENDDO
464 ENDDO
465 ENDDO
466 ELSE
467 DO bj = myByLo(myThid), myByHi(myThid)
468 DO bi = myBxLo(myThid), myBxHi(myThid)
469 DO j=1-Oly,sNy+Oly
470 DO i=1-Olx,sNx+Olx
471 atemp(i,j,bi,bj) = aWghtFlux * atemp0(i,j,bi,bj) +
472 & bWghtFlux * atemp1(i,j,bi,bj)
473 aqh(i,j,bi,bj) = aWghtFlux * aqh0(i,j,bi,bj) +
474 & bWghtFlux * aqh1(i,j,bi,bj)
475 lwdown(i,j,bi,bj) = aWghtFlux * lwdown0(i,j,bi,bj) +
476 & bWghtFlux * lwdown1(i,j,bi,bj)
477 swdown(i,j,bi,bj) = aWghtFlux * swdown0(i,j,bi,bj) +
478 & bWghtFlux * swdown1(i,j,bi,bj)
479 precip(i,j,bi,bj) = aWghtFlux * precip0(i,j,bi,bj) +
480 & bWghtFlux * precip1(i,j,bi,bj)
481 evap(i,j,bi,bj) = aWghtFlux * evap0(i,j,bi,bj) +
482 & bWghtFlux * evap1(i,j,bi,bj)
483 runoff(i,j,bi,bj) = aWghtFlux * runoff0(i,j,bi,bj) +
484 & bWghtFlux * runoff1(i,j,bi,bj)
485 ENDDO
486 ENDDO
487 ENDDO
488 ENDDO
489 ENDIF
490
491 C-- Time interpolation of SSS forcing variables.
492 IF (SSS0_is_first) THEN
493 DO bj = myByLo(myThid), myByHi(myThid)
494 DO bi = myBxLo(myThid), myBxHi(myThid)
495 DO j=1-Oly,sNy+Oly
496 DO i=1-Olx,sNx+Olx
497 SSS(i,j,bi,bj) = bWghtSSS * SSSsi0(i,j,bi,bj) +
498 & aWghtSSS * SSSsi1(i,j,bi,bj)
499 ENDDO
500 ENDDO
501 ENDDO
502 ENDDO
503 ELSE
504 DO bj = myByLo(myThid), myByHi(myThid)
505 DO bi = myBxLo(myThid), myBxHi(myThid)
506 DO j=1-Oly,sNy+Oly
507 DO i=1-Olx,sNx+Olx
508 SSS(i,j,bi,bj) = aWghtSSS * SSSsi0(i,j,bi,bj) +
509 & bWghtSSS * SSSsi1(i,j,bi,bj)
510 ENDDO
511 ENDDO
512 ENDDO
513 ENDDO
514 ENDIF
515
516 C-- Time interpolation of SST forcing variables.
517 IF (SST0_is_first) THEN
518 DO bj = myByLo(myThid), myByHi(myThid)
519 DO bi = myBxLo(myThid), myBxHi(myThid)
520 DO j=1-Oly,sNy+Oly
521 DO i=1-Olx,sNx+Olx
522 SST(i,j,bi,bj) = bWghtSST * SSTsi0(i,j,bi,bj) +
523 & aWghtSST * SSTsi1(i,j,bi,bj)
524 ENDDO
525 ENDDO
526 ENDDO
527 ENDDO
528 ELSE
529 DO bj = myByLo(myThid), myByHi(myThid)
530 DO bi = myBxLo(myThid), myBxHi(myThid)
531 DO j=1-Oly,sNy+Oly
532 DO i=1-Olx,sNx+Olx
533 SST(i,j,bi,bj) = aWghtSST * SSTsi0(i,j,bi,bj) +
534 & bWghtSST * SSTsi1(i,j,bi,bj)
535 ENDDO
536 ENDDO
537 ENDDO
538 ENDDO
539 ENDIF
540
541 #endif /* SEAICE_EXTERNAL_FORCING */
542
543 RETURN
544 END
545
546
547 C=======================================================================
548
549 SUBROUTINE INIT_ARRAY_RS( arr, initValue, myThid )
550 C This routine sets the RS array arr to initValue
551 IMPLICIT NONE
552 C === Global variables ===
553 #include "SIZE.h"
554 #include "EEPARAMS.h"
555 C === Arguments ===
556 _RS arr (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
557 _RS initValue
558 INTEGER myThid
559
560 #ifndef SEAICE_EXTERNAL_FORCING
561
562 C === Local variables ===
563 INTEGER i,j,bi,bj
564 C
565 DO bj = myByLo(myThid), myByHi(myThid)
566 DO bi = myBxLo(myThid), myBxHi(myThid)
567 DO j = 1-Oly,sNy+Oly
568 DO i = 1-Olx,sNx+Olx
569 arr(i,j,bi,bj) = initValue
570 ENDDO
571 ENDDO
572 ENDDO
573 ENDDO
574
575 #endif /* SEAICE_EXTERNAL_FORCING */
576
577 RETURN
578 END

  ViewVC Help
Powered by ViewVC 1.1.22