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

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

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

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

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.2

  ViewVC Help
Powered by ViewVC 1.1.22