/[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.3 by dimitri, Thu Dec 5 08:43:03 2002 UTC revision 1.4 by dimitri, Sat Dec 28 10:11:11 2002 UTC
# Line 6  CStartOfInterface Line 6  CStartOfInterface
6        SUBROUTINE SEAICE_GET_FORCING( myTime, myIter, myThid )        SUBROUTINE SEAICE_GET_FORCING( myTime, myIter, myThid )
7  C     /==========================================================\  C     /==========================================================\
8  C     | SUBROUTINE SEAICE_GET_FORCING                            |  C     | SUBROUTINE SEAICE_GET_FORCING                            |
9  C     | o Load wind, thermal, and evaporation minus              |  C     | o Load atmospheric state and runoff.                     |
 C     |   precipitation fields for sea ice model.                |  
10  C     |==========================================================|  C     |==========================================================|
11  C     \==========================================================/  C     \==========================================================/
12        IMPLICIT NONE        IMPLICIT NONE
# Line 33  CEndOfInterface Line 32  CEndOfInterface
32        EXTERNAL ILNBLNK        EXTERNAL ILNBLNK
33    
34  #ifdef ALLOW_SEAICE  #ifdef ALLOW_SEAICE
35    #ifndef SEAICE_EXTERNAL_FORCING
36    
37  C     === Local arrays ===  C     === Local arrays ===
38        COMMON /TDFIELDS_FLAGS/        COMMON /TDFIELDS_FLAGS/
# Line 94  C--   Check to see whether myTime is out Line 94  C--   Check to see whether myTime is out
94  C--   First call requires that we initialize everything for safety  C--   First call requires that we initialize everything for safety
95        IF ( myIter .EQ. nIter0 ) THEN        IF ( myIter .EQ. nIter0 ) THEN
96         initValue = ZERO         initValue = ZERO
97         CALL INIT_ARRAY_RS( gairx0 , initValue, myThid )         CALL INIT_ARRAY_RS( uwind0  , initValue, myThid )
98         CALL INIT_ARRAY_RS( gairx1 , initValue, myThid )         CALL INIT_ARRAY_RS( uwind1  , initValue, myThid )
99         CALL INIT_ARRAY_RS( gairy0 , initValue, myThid )         CALL INIT_ARRAY_RS( vwind0  , initValue, myThid )
100         CALL INIT_ARRAY_RS( gairy1 , initValue, myThid )         CALL INIT_ARRAY_RS( vwind1  , initValue, myThid )
101         initValue = 283. _d 0         initValue = 283. _d 0
102         CALL INIT_ARRAY_RS( tair0  , initValue, myThid )         CALL INIT_ARRAY_RS( atemp0  , initValue, myThid )
103         CALL INIT_ARRAY_RS( tair1  , initValue, myThid )         CALL INIT_ARRAY_RS( atemp1  , initValue, myThid )
104         initValue = 0.005 _d 0         initValue = 0.005 _d 0
105         CALL INIT_ARRAY_RS( qa0    , initValue, myThid )         CALL INIT_ARRAY_RS( aqh0    , initValue, myThid )
106         CALL INIT_ARRAY_RS( qa1    , initValue, myThid )         CALL INIT_ARRAY_RS( aqh1    , initValue, myThid )
107         initValue = 300. _d 0         initValue = 300. _d 0
108         CALL INIT_ARRAY_RS( flo0   , initValue, myThid )         CALL INIT_ARRAY_RS( lwflux0 , initValue, myThid )
109         CALL INIT_ARRAY_RS( flo1   , initValue, myThid )         CALL INIT_ARRAY_RS( lwflux1 , initValue, myThid )
110         initValue = 200. _d 0         initValue = 200. _d 0
111         CALL INIT_ARRAY_RS( fsh0   , initValue, myThid )         CALL INIT_ARRAY_RS( swflux0 , initValue, myThid )
112         CALL INIT_ARRAY_RS( fsh1   , initValue, myThid )         CALL INIT_ARRAY_RS( swflux1 , initValue, myThid )
113         initValue = ZERO         initValue = ZERO
114         CALL INIT_ARRAY_RS( rain0  , initValue, myThid )         CALL INIT_ARRAY_RS( precip0 , initValue, myThid )
115         CALL INIT_ARRAY_RS( rain1  , initValue, myThid )         CALL INIT_ARRAY_RS( precip1 , initValue, myThid )
116         CALL INIT_ARRAY_RS( evap0  , initValue, myThid )         CALL INIT_ARRAY_RS( evap0   , initValue, myThid )
117         CALL INIT_ARRAY_RS( evap1  , initValue, myThid )         CALL INIT_ARRAY_RS( evap1   , initValue, myThid )
118         CALL INIT_ARRAY_RS( runoff0, initValue, myThid )         CALL INIT_ARRAY_RS( runoff0 , initValue, myThid )
119         CALL INIT_ARRAY_RS( runoff1, initValue, myThid )         CALL INIT_ARRAY_RS( runoff1 , initValue, myThid )
120         initValue = 35. _d 0         initValue = 35. _d 0
121         CALL INIT_ARRAY_RS( SSSsi0   , initValue, myThid )         CALL INIT_ARRAY_RS( SSSsi0  , initValue, myThid )
122         CALL INIT_ARRAY_RS( SSSsi1   , initValue, myThid )         CALL INIT_ARRAY_RS( SSSsi1  , initValue, myThid )
123         initValue = 10. _d 0         initValue = 10. _d 0
124         CALL INIT_ARRAY_RS( SSTsi0   , initValue, myThid )         CALL INIT_ARRAY_RS( SSTsi0  , initValue, myThid )
125         CALL INIT_ARRAY_RS( SSTsi1   , initValue, myThid )         CALL INIT_ARRAY_RS( SSTsi1  , initValue, myThid )
126    
127         wind0_is_first = .TRUE.         wind0_is_first = .TRUE.
128         flux0_is_first = .TRUE.         flux0_is_first = .TRUE.
# Line 134  C--   First call requires that we initia Line 134  C--   First call requires that we initia
134       &  'S/R SEAICE_GET_FORCING: initialize',myTime,myIter       &  'S/R SEAICE_GET_FORCING: initialize',myTime,myIter
135    
136         iRec = int((YearTime-WindForcingStart)/WindForcingPeriod) + 1         iRec = int((YearTime-WindForcingStart)/WindForcingPeriod) + 1
137         IF ( gairxFile .NE. ' ' ) THEN         IF ( uwindFile .NE. ' ' ) THEN
138          iEnd = ILNBLNK( gairxFile ) - 2          iEnd = ILNBLNK( uwindFile ) - 2
139          WRITE(fName,'(A,I2.2)') gairxFile(1:iEnd), CurrentYear2          WRITE(fName,'(A,I2.2)') uwindFile(1:iEnd), CurrentYear2
140          CALL READ_REC_XY_RS( fName,gairx0,iRec  ,myIter,myThid )          CALL READ_REC_XY_RS( fName,uwind0,iRec  ,myIter,myThid )
141          CALL READ_REC_XY_RS( fName,gairx1,iRec+1,myIter,myThid )          CALL READ_REC_XY_RS( fName,uwind1,iRec+1,myIter,myThid )
142         ENDIF         ENDIF
143         IF ( gairyFile .NE. ' ' ) THEN         IF ( vwindFile .NE. ' ' ) THEN
144          iEnd = ILNBLNK( gairyFile ) - 2          iEnd = ILNBLNK( vwindFile ) - 2
145          WRITE(fName,'(A,I2.2)') gairyFile(1:iEnd), CurrentYear2          WRITE(fName,'(A,I2.2)') vwindFile(1:iEnd), CurrentYear2
146          CALL READ_REC_XY_RS( fName,gairy0,iRec  ,myIter,myThid )          CALL READ_REC_XY_RS( fName,vwind0,iRec  ,myIter,myThid )
147          CALL READ_REC_XY_RS( fName,gairy1,iRec+1,myIter,myThid )          CALL READ_REC_XY_RS( fName,vwind1,iRec+1,myIter,myThid )
148         ENDIF         ENDIF
149    
150         iRec = int((YearTime-FluxForcingStart)/FluxForcingPeriod) + 1         iRec = int((YearTime-FluxForcingStart)/FluxForcingPeriod) + 1
151         IF ( tairFile .NE. ' ' ) THEN         IF ( atempFile .NE. ' ' ) THEN
152          iEnd = ILNBLNK( tairFile ) - 4          iEnd = ILNBLNK( atempFile ) - 4
153          WRITE(fName,'(A,I4.4)') tairFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') atempFile(1:iEnd), CurrentYear
154          CALL READ_REC_XY_RS( fName,tair0,iRec  ,myIter,myThid )          CALL READ_REC_XY_RS( fName,atemp0,iRec  ,myIter,myThid )
155          CALL READ_REC_XY_RS( fName,tair1,iRec+1,myIter,myThid )          CALL READ_REC_XY_RS( fName,atemp1,iRec+1,myIter,myThid )
156         ENDIF         ENDIF
157         IF ( qaFile .NE. ' ' ) THEN         IF ( aqhFile .NE. ' ' ) THEN
158          iEnd = ILNBLNK( qaFile ) - 4          iEnd = ILNBLNK( aqhFile ) - 4
159          WRITE(fName,'(A,I4.4)') qaFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') aqhFile(1:iEnd), CurrentYear
160          CALL READ_REC_XY_RS( fName,qa0,iRec  ,myIter,myThid )          CALL READ_REC_XY_RS( fName,aqh0,iRec  ,myIter,myThid )
161          CALL READ_REC_XY_RS( fName,qa1,iRec+1,myIter,myThid )          CALL READ_REC_XY_RS( fName,aqh1,iRec+1,myIter,myThid )
162         ENDIF         ENDIF
163         IF ( floFile .NE. ' ' ) THEN         IF ( lwfluxFile .NE. ' ' ) THEN
164          iEnd = ILNBLNK( floFile ) - 4          iEnd = ILNBLNK( lwfluxFile ) - 4
165          WRITE(fName,'(A,I4.4)') floFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') lwfluxFile(1:iEnd), CurrentYear
166          CALL READ_REC_XY_RS( fName,flo0,iRec  ,myIter,myThid )          CALL READ_REC_XY_RS( fName,lwflux0,iRec  ,myIter,myThid )
167          CALL READ_REC_XY_RS( fName,flo1,iRec+1,myIter,myThid )          CALL READ_REC_XY_RS( fName,lwflux1,iRec+1,myIter,myThid )
168         ENDIF         ENDIF
169         IF ( fshFile .NE. ' ' ) THEN         IF ( swfluxFile .NE. ' ' ) THEN
170          iEnd = ILNBLNK( fshFile ) - 4          iEnd = ILNBLNK( swfluxFile ) - 4
171          WRITE(fName,'(A,I4.4)') fshFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') swfluxFile(1:iEnd), CurrentYear
172          CALL READ_REC_XY_RS( fName,fsh0,iRec  ,myIter,myThid )          CALL READ_REC_XY_RS( fName,swflux0,iRec  ,myIter,myThid )
173          CALL READ_REC_XY_RS( fName,fsh1,iRec+1,myIter,myThid )          CALL READ_REC_XY_RS( fName,swflux1,iRec+1,myIter,myThid )
174         ENDIF         ENDIF
175         IF ( rainFile .NE. ' ' ) THEN         IF ( precipFile .NE. ' ' ) THEN
176          iEnd = ILNBLNK( rainFile ) - 4          iEnd = ILNBLNK( precipFile ) - 4
177          WRITE(fName,'(A,I4.4)') rainFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') precipFile(1:iEnd), CurrentYear
178          CALL READ_REC_XY_RS( fName,rain0,iRec  ,myIter,myThid )          CALL READ_REC_XY_RS( fName,precip0,iRec  ,myIter,myThid )
179          CALL READ_REC_XY_RS( fName,rain1,iRec+1,myIter,myThid )          CALL READ_REC_XY_RS( fName,precip1,iRec+1,myIter,myThid )
180         ENDIF         ENDIF
181         IF ( evapFile .NE. ' ' ) THEN         IF ( evapFile .NE. ' ' ) THEN
182          iEnd = ILNBLNK( evapFile ) - 4          iEnd = ILNBLNK( evapFile ) - 4
# Line 207  C--   First call requires that we initia Line 207  C--   First call requires that we initia
207    
208         _END_MASTER(myThid)         _END_MASTER(myThid)
209    
210         _EXCH_XY_R4( gairx0, myThid )         _EXCH_XY_R4( uwind0,  myThid )
211         _EXCH_XY_R4( gairx1, myThid )         _EXCH_XY_R4( uwind1,  myThid )
212         _EXCH_XY_R4( gairy0, myThid )         _EXCH_XY_R4( vwind0,  myThid )
213         _EXCH_XY_R4( gairy1, myThid )         _EXCH_XY_R4( vwind1,  myThid )
214         _EXCH_XY_R4( tair0,  myThid )         _EXCH_XY_R4( atemp0,  myThid )
215         _EXCH_XY_R4( tair1,  myThid )         _EXCH_XY_R4( atemp1,  myThid )
216         _EXCH_XY_R4( qa0,    myThid )         _EXCH_XY_R4( aqh0,    myThid )
217         _EXCH_XY_R4( qa1,    myThid )         _EXCH_XY_R4( aqh1,    myThid )
218         _EXCH_XY_R4( flo0,   myThid )         _EXCH_XY_R4( lwflux0, myThid )
219         _EXCH_XY_R4( flo1,   myThid )         _EXCH_XY_R4( lwflux1, myThid )
220         _EXCH_XY_R4( fsh0,   myThid )         _EXCH_XY_R4( swflux0, myThid )
221         _EXCH_XY_R4( fsh1,   myThid )         _EXCH_XY_R4( swflux1, myThid )
222         _EXCH_XY_R4( rain0,  myThid )         _EXCH_XY_R4( precip0, myThid )
223         _EXCH_XY_R4( rain1,  myThid )         _EXCH_XY_R4( precip1, myThid )
224         _EXCH_XY_R4( evap0,  myThid )         _EXCH_XY_R4( evap0,   myThid )
225         _EXCH_XY_R4( evap1,  myThid )         _EXCH_XY_R4( evap1,   myThid )
226         _EXCH_XY_R4( runoff0,myThid )         _EXCH_XY_R4( runoff0, myThid )
227         _EXCH_XY_R4( runoff1,myThid )         _EXCH_XY_R4( runoff1, myThid )
228         _EXCH_XY_R4( SSTsi0,   myThid )         _EXCH_XY_R4( SSTsi0,  myThid )
229         _EXCH_XY_R4( SSTsi1,   myThid )         _EXCH_XY_R4( SSTsi1,  myThid )
230         _EXCH_XY_R4( SSSsi0,   myThid )         _EXCH_XY_R4( SSSsi0,  myThid )
231         _EXCH_XY_R4( SSSsi1,   myThid )         _EXCH_XY_R4( SSSsi1,  myThid )
232    
233        ENDIF        ENDIF
234    
# Line 241  C--   Now calculate whether if it is tim Line 241  C--   Now calculate whether if it is tim
241         _BEGIN_MASTER(myThid)         _BEGIN_MASTER(myThid)
242         write(0,*)         write(0,*)
243       &  'S/R SEAICE_GET_FORCING: reading winds',myTime,myIter       &  'S/R SEAICE_GET_FORCING: reading winds',myTime,myIter
244         IF ( gairxFile .NE. ' ' ) THEN         IF ( uwindFile .NE. ' ' ) THEN
245          iEnd = ILNBLNK( gairxFile ) - 2          iEnd = ILNBLNK( uwindFile ) - 2
246          WRITE(fName,'(A,I2.2)') gairxFile(1:iEnd), CurrentYear2          WRITE(fName,'(A,I2.2)') uwindFile(1:iEnd), CurrentYear2
247          IF (wind0_is_first) THEN          IF (wind0_is_first) THEN
248           CALL READ_REC_XY_RS( fName,gairx0,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,uwind0,iRec,myIter,myThid )
249          ELSE          ELSE
250           CALL READ_REC_XY_RS( fName,gairx1,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,uwind1,iRec,myIter,myThid )
251          ENDIF          ENDIF
252         ENDIF         ENDIF
253         IF ( gairyFile .NE. ' ' ) THEN         IF ( vwindFile .NE. ' ' ) THEN
254          iEnd = ILNBLNK( gairyFile ) - 2          iEnd = ILNBLNK( vwindFile ) - 2
255          WRITE(fName,'(A,I2.2)') gairyFile(1:iEnd), CurrentYear2          WRITE(fName,'(A,I2.2)') vwindFile(1:iEnd), CurrentYear2
256          IF (wind0_is_first) THEN          IF (wind0_is_first) THEN
257           CALL READ_REC_XY_RS( fName,gairy0,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,vwind0,iRec,myIter,myThid )
258          ELSE          ELSE
259           CALL READ_REC_XY_RS( fName,gairy1,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,vwind1,iRec,myIter,myThid )
260          ENDIF          ENDIF
261         ENDIF         ENDIF
262         _END_MASTER(myThid)         _END_MASTER(myThid)
263         IF (wind0_is_first) THEN         IF (wind0_is_first) THEN
264          _EXCH_XY_R4( gairx0, myThid )          _EXCH_XY_R4( uwind0, myThid )
265          _EXCH_XY_R4( gairy0, myThid )          _EXCH_XY_R4( vwind0, myThid )
266          wind0_is_first=.FALSE.          wind0_is_first=.FALSE.
267         ELSE         ELSE
268          _EXCH_XY_R4( gairx1, myThid )          _EXCH_XY_R4( uwind1, myThid )
269          _EXCH_XY_R4( gairy1, myThid )          _EXCH_XY_R4( vwind1, myThid )
270          wind0_is_first=.TRUE.          wind0_is_first=.TRUE.
271         ENDIF         ENDIF
272        ENDIF        ENDIF
# Line 280  C--   Now calculate whether if it is tim Line 280  C--   Now calculate whether if it is tim
280         _BEGIN_MASTER(myThid)         _BEGIN_MASTER(myThid)
281         write(0,*)         write(0,*)
282       &  'S/R SEAICE_GET_FORCING: reading fluxes',myTime,myIter       &  'S/R SEAICE_GET_FORCING: reading fluxes',myTime,myIter
283         IF ( tairFile .NE. ' ' ) THEN         IF ( atempFile .NE. ' ' ) THEN
284          iEnd = ILNBLNK( tairFile ) - 4          iEnd = ILNBLNK( atempFile ) - 4
285          WRITE(fName,'(A,I4.4)') tairFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') atempFile(1:iEnd), CurrentYear
286          IF (flux0_is_first) THEN          IF (flux0_is_first) THEN
287           CALL READ_REC_XY_RS( fName,tair0,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,atemp0,iRec,myIter,myThid )
288          ELSE          ELSE
289           CALL READ_REC_XY_RS( fName,tair1,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,atemp1,iRec,myIter,myThid )
290          ENDIF          ENDIF
291         ENDIF         ENDIF
292         IF ( qaFile .NE. ' ' ) THEN         IF ( aqhFile .NE. ' ' ) THEN
293          iEnd = ILNBLNK( qaFile ) - 4          iEnd = ILNBLNK( aqhFile ) - 4
294          WRITE(fName,'(A,I4.4)') qaFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') aqhFile(1:iEnd), CurrentYear
295          IF (flux0_is_first) THEN          IF (flux0_is_first) THEN
296           CALL READ_REC_XY_RS( fName,qa0,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,aqh0,iRec,myIter,myThid )
297          ELSE          ELSE
298           CALL READ_REC_XY_RS( fName,qa1,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,aqh1,iRec,myIter,myThid )
299          ENDIF          ENDIF
300         ENDIF         ENDIF
301         IF ( floFile .NE. ' ' ) THEN         IF ( lwfluxFile .NE. ' ' ) THEN
302          iEnd = ILNBLNK( floFile ) - 4          iEnd = ILNBLNK( lwfluxFile ) - 4
303          WRITE(fName,'(A,I4.4)') floFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') lwfluxFile(1:iEnd), CurrentYear
304          IF (flux0_is_first) THEN          IF (flux0_is_first) THEN
305           CALL READ_REC_XY_RS( fName,flo0,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,lwflux0,iRec,myIter,myThid )
306          ELSE          ELSE
307           CALL READ_REC_XY_RS( fName,flo1,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,lwflux1,iRec,myIter,myThid )
308          ENDIF          ENDIF
309         ENDIF         ENDIF
310         IF ( fshFile .NE. ' ' ) THEN         IF ( swfluxFile .NE. ' ' ) THEN
311          iEnd = ILNBLNK( fshFile ) - 4          iEnd = ILNBLNK( swfluxFile ) - 4
312          WRITE(fName,'(A,I4.4)') fshFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') swfluxFile(1:iEnd), CurrentYear
313          IF (flux0_is_first) THEN          IF (flux0_is_first) THEN
314           CALL READ_REC_XY_RS( fName,fsh0,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,swflux0,iRec,myIter,myThid )
315          ELSE          ELSE
316           CALL READ_REC_XY_RS( fName,fsh1,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,swflux1,iRec,myIter,myThid )
317          ENDIF          ENDIF
318         ENDIF         ENDIF
319         IF ( rainFile .NE. ' ' ) THEN         IF ( precipFile .NE. ' ' ) THEN
320          iEnd = ILNBLNK( rainFile ) - 4          iEnd = ILNBLNK( precipFile ) - 4
321          WRITE(fName,'(A,I4.4)') rainFile(1:iEnd), CurrentYear          WRITE(fName,'(A,I4.4)') precipFile(1:iEnd), CurrentYear
322          IF (flux0_is_first) THEN          IF (flux0_is_first) THEN
323           CALL READ_REC_XY_RS( fName,rain0,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,precip0,iRec,myIter,myThid )
324          ELSE          ELSE
325           CALL READ_REC_XY_RS( fName,rain1,iRec,myIter,myThid )           CALL READ_REC_XY_RS( fName,precip1,iRec,myIter,myThid )
326          ENDIF          ENDIF
327         ENDIF         ENDIF
328         IF ( evapFile .NE. ' ' ) THEN         IF ( evapFile .NE. ' ' ) THEN
# Line 345  C--   Now calculate whether if it is tim Line 345  C--   Now calculate whether if it is tim
345         ENDIF         ENDIF
346         _END_MASTER(myThid)         _END_MASTER(myThid)
347         IF (flux0_is_first) THEN         IF (flux0_is_first) THEN
348          _EXCH_XY_R4(tair0,  myThid )          _EXCH_XY_R4(atemp0,  myThid )
349          _EXCH_XY_R4(qa0,    myThid )          _EXCH_XY_R4(aqh0,    myThid )
350          _EXCH_XY_R4(flo0,   myThid )          _EXCH_XY_R4(lwflux0, myThid )
351          _EXCH_XY_R4(fsh0,   myThid )          _EXCH_XY_R4(swflux0, myThid )
352          _EXCH_XY_R4(rain0,  myThid )          _EXCH_XY_R4(precip0, myThid )
353          _EXCH_XY_R4(evap0,  myThid )          _EXCH_XY_R4(evap0,   myThid )
354          _EXCH_XY_R4(runoff0,myThid )          _EXCH_XY_R4(runoff0, myThid )
355          flux0_is_first=.FALSE.          flux0_is_first=.FALSE.
356         ELSE         ELSE
357          _EXCH_XY_R4(tair1,  myThid )          _EXCH_XY_R4(atemp1,  myThid )
358          _EXCH_XY_R4(qa1,    myThid )          _EXCH_XY_R4(aqh1,    myThid )
359          _EXCH_XY_R4(flo1,   myThid )          _EXCH_XY_R4(lwflux1, myThid )
360          _EXCH_XY_R4(fsh1,   myThid )          _EXCH_XY_R4(swflux1, myThid )
361          _EXCH_XY_R4(rain1,  myThid )          _EXCH_XY_R4(precip1, myThid )
362          _EXCH_XY_R4(evap1,  myThid )          _EXCH_XY_R4(evap1,   myThid )
363          _EXCH_XY_R4(runoff1,myThid )          _EXCH_XY_R4(runoff1, myThid )
364          flux0_is_first=.TRUE.          flux0_is_first=.TRUE.
365         ENDIF         ENDIF
366        ENDIF        ENDIF
# Line 419  C--   Time interpolation of wind forcing Line 419  C--   Time interpolation of wind forcing
419          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
420           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
421            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
422             gairx(i,j,bi,bj) = bWghtWind *  gairx0(i,j,bi,bj) +             uwind(i,j,bi,bj) = bWghtWind *  uwind0(i,j,bi,bj) +
423       &                        aWghtWind *  gairx1(i,j,bi,bj)       &                        aWghtWind *  uwind1(i,j,bi,bj)
424             gairy(i,j,bi,bj) = bWghtWind *  gairy0(i,j,bi,bj) +             vwind(i,j,bi,bj) = bWghtWind *  vwind0(i,j,bi,bj) +
425       &                        aWghtWind *  gairy1(i,j,bi,bj)       &                        aWghtWind *  vwind1(i,j,bi,bj)
426            ENDDO            ENDDO
427           ENDDO           ENDDO
428          ENDDO          ENDDO
# Line 432  C--   Time interpolation of wind forcing Line 432  C--   Time interpolation of wind forcing
432          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
433           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
434            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
435             gairx(i,j,bi,bj) = aWghtWind *  gairx0(i,j,bi,bj) +             uwind(i,j,bi,bj) = aWghtWind *  uwind0(i,j,bi,bj) +
436       &                        bWghtWind *  gairx1(i,j,bi,bj)       &                        bWghtWind *  uwind1(i,j,bi,bj)
437             gairy(i,j,bi,bj) = aWghtWind *  gairy0(i,j,bi,bj) +             vwind(i,j,bi,bj) = aWghtWind *  vwind0(i,j,bi,bj) +
438       &                        bWghtWind *  gairy1(i,j,bi,bj)       &                        bWghtWind *  vwind1(i,j,bi,bj)
439            ENDDO            ENDDO
440           ENDDO           ENDDO
441          ENDDO          ENDDO
# Line 448  C--   Time interpolation of flux forcing Line 448  C--   Time interpolation of flux forcing
448          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
449           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
450            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
451            tair(i,j,bi,bj)  = bWghtFlux *   tair0(i,j,bi,bj) +            atemp(i,j,bi,bj)  = bWghtFlux *  atemp0(i,j,bi,bj) +
452       &                       aWghtFlux *   tair1(i,j,bi,bj)       &                        aWghtFlux *  atemp1(i,j,bi,bj)
453            qa(i,j,bi,bj)    = bWghtFlux *     qa0(i,j,bi,bj) +            aqh(i,j,bi,bj)    = bWghtFlux *    aqh0(i,j,bi,bj) +
454       &                       aWghtFlux *     qa1(i,j,bi,bj)       &                        aWghtFlux *    aqh1(i,j,bi,bj)
455            flo(i,j,bi,bj)   = bWghtFlux *    flo0(i,j,bi,bj) +            lwflux(i,j,bi,bj) = bWghtFlux * lwflux0(i,j,bi,bj) +
456       &                       aWghtFlux *    flo1(i,j,bi,bj)       &                        aWghtFlux * lwflux1(i,j,bi,bj)
457            fsh(i,j,bi,bj)   = bWghtFlux *    fsh0(i,j,bi,bj) +            swflux(i,j,bi,bj) = bWghtFlux * swflux0(i,j,bi,bj) +
458       &                       aWghtFlux *    fsh1(i,j,bi,bj)       &                        aWghtFlux * swflux1(i,j,bi,bj)
459            rain(i,j,bi,bj)  = bWghtFlux *   rain0(i,j,bi,bj) +            precip(i,j,bi,bj) = bWghtFlux * precip0(i,j,bi,bj) +
460       &                       aWghtFlux *   rain1(i,j,bi,bj)       &                        aWghtFlux *   precip1(i,j,bi,bj)
461            evap(i,j,bi,bj)  = bWghtFlux *   evap0(i,j,bi,bj) +            evap(i,j,bi,bj)   = bWghtFlux *   evap0(i,j,bi,bj) +
462       &                       aWghtFlux *   evap1(i,j,bi,bj)       &                        aWghtFlux *   evap1(i,j,bi,bj)
463            runoff(i,j,bi,bj)= bWghtFlux * runoff0(i,j,bi,bj) +            runoff(i,j,bi,bj) = bWghtFlux * runoff0(i,j,bi,bj) +
464       &                       aWghtFlux * runoff1(i,j,bi,bj)       &                        aWghtFlux * runoff1(i,j,bi,bj)
465            ENDDO            ENDDO
466           ENDDO           ENDDO
467          ENDDO          ENDDO
# Line 471  C--   Time interpolation of flux forcing Line 471  C--   Time interpolation of flux forcing
471          DO bi = myBxLo(myThid), myBxHi(myThid)          DO bi = myBxLo(myThid), myBxHi(myThid)
472           DO j=1-Oly,sNy+Oly           DO j=1-Oly,sNy+Oly
473            DO i=1-Olx,sNx+Olx            DO i=1-Olx,sNx+Olx
474            tair(i,j,bi,bj)  = aWghtFlux *   tair0(i,j,bi,bj) +            atemp(i,j,bi,bj)  = aWghtFlux *  atemp0(i,j,bi,bj) +
475       &                       bWghtFlux *   tair1(i,j,bi,bj)       &                        bWghtFlux *  atemp1(i,j,bi,bj)
476            qa(i,j,bi,bj)    = aWghtFlux *     qa0(i,j,bi,bj) +            aqh(i,j,bi,bj)    = aWghtFlux *    aqh0(i,j,bi,bj) +
477       &                       bWghtFlux *     qa1(i,j,bi,bj)       &                        bWghtFlux *    aqh1(i,j,bi,bj)
478            flo(i,j,bi,bj)   = aWghtFlux *    flo0(i,j,bi,bj) +            lwflux(i,j,bi,bj) = aWghtFlux * lwflux0(i,j,bi,bj) +
479       &                       bWghtFlux *    flo1(i,j,bi,bj)       &                        bWghtFlux * lwflux1(i,j,bi,bj)
480            fsh(i,j,bi,bj)   = aWghtFlux *    fsh0(i,j,bi,bj) +            swflux(i,j,bi,bj) = aWghtFlux * swflux0(i,j,bi,bj) +
481       &                       bWghtFlux *    fsh1(i,j,bi,bj)       &                        bWghtFlux * swflux1(i,j,bi,bj)
482            rain(i,j,bi,bj)  = aWghtFlux *   rain0(i,j,bi,bj) +            precip(i,j,bi,bj) = aWghtFlux * precip0(i,j,bi,bj) +
483       &                       bWghtFlux *   rain1(i,j,bi,bj)       &                        bWghtFlux * precip1(i,j,bi,bj)
484            evap(i,j,bi,bj)  = aWghtFlux *   evap0(i,j,bi,bj) +            evap(i,j,bi,bj)   = aWghtFlux *   evap0(i,j,bi,bj) +
485       &                       bWghtFlux *   evap1(i,j,bi,bj)       &                        bWghtFlux *   evap1(i,j,bi,bj)
486            runoff(i,j,bi,bj)= aWghtFlux * runoff0(i,j,bi,bj) +            runoff(i,j,bi,bj) = aWghtFlux * runoff0(i,j,bi,bj) +
487       &                       bWghtFlux * runoff1(i,j,bi,bj)       &                        bWghtFlux * runoff1(i,j,bi,bj)
488            ENDDO            ENDDO
489           ENDDO           ENDDO
490          ENDDO          ENDDO
# Line 541  C--   Time interpolation of SST forcing Line 541  C--   Time interpolation of SST forcing
541         ENDDO         ENDDO
542        ENDIF        ENDIF
543    
544    #endif SEAICE_EXTERNAL_FORCING
545  #endif ALLOW_SEAICE  #endif ALLOW_SEAICE
546    
547        RETURN        RETURN
# Line 561  C     === Arguments === Line 562  C     === Arguments ===
562        INTEGER myThid        INTEGER myThid
563    
564  #ifdef ALLOW_SEAICE  #ifdef ALLOW_SEAICE
565    #ifndef SEAICE_EXTERNAL_FORCING
566    
567  C     === Local variables ===  C     === Local variables ===
568        INTEGER i,j,bi,bj        INTEGER i,j,bi,bj
# Line 575  C Line 577  C
577         ENDDO         ENDDO
578        ENDDO        ENDDO
579    
580    #endif SEAICE_EXTERNAL_FORCING
581  #endif ALLOW_SEAICE  #endif ALLOW_SEAICE
582    
583        RETURN        RETURN

Legend:
Removed from v.1.3  
changed lines
  Added in v.1.4

  ViewVC Help
Powered by ViewVC 1.1.22