/[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.7 - (show annotations) (download)
Sun Dec 14 04:56:18 2003 UTC (20 years, 6 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint53f_post, checkpoint54a_pre, checkpoint55c_post, checkpoint53b_pre, checkpoint52l_pre, checkpoint52e_pre, hrcube4, checkpoint52n_post, checkpoint52j_post, checkpoint52e_post, checkpoint57b_post, checkpoint53c_post, checkpoint53d_post, checkpoint55d_pre, checkpoint57a_post, checkpoint55j_post, checkpoint56b_post, checkpoint52j_pre, checkpoint54a_post, checkpoint52l_post, checkpoint55h_post, checkpoint52k_post, checkpoint54b_post, checkpoint54d_post, checkpoint56c_post, checkpoint54e_post, checkpoint55b_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint55a_post, hrcube5, checkpoint53b_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint54, checkpoint57, checkpoint56, checkpoint53, checkpoint52d_post, checkpoint53g_post, checkpoint52f_post, checkpoint54f_post, checkpoint53d_pre, checkpoint55e_post, checkpoint54c_post, checkpoint52i_post, checkpoint55i_post, checkpoint52i_pre, checkpoint52h_pre, checkpoint52f_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint56a_post, checkpoint55d_post
Changes since 1.6: +5 -9 lines
added "exch_uv" exchanges to pkg/seaice

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

  ViewVC Help
Powered by ViewVC 1.1.22