/[MITgcm]/MITgcm_contrib/darwin2/pkg/darwin/darwin_fields_load.F
ViewVC logotype

Annotation of /MITgcm_contrib/darwin2/pkg/darwin/darwin_fields_load.F

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


Revision 1.7 - (hide annotations) (download)
Wed Dec 4 21:21:49 2013 UTC (11 years, 7 months ago) by jahn
Branch: MAIN
Changes since 1.6: +3 -1 lines
add some barriers

1 jahn 1.7 C $Header: /u/gcmpack/MITgcm_contrib/darwin2/pkg/darwin/darwin_fields_load.F,v 1.6 2013/11/22 21:04:07 jahn Exp $
2 jahn 1.2 C $Name: $
3 jahn 1.1
4     #include "CPP_OPTIONS.h"
5     #include "PTRACERS_OPTIONS.h"
6     #include "DARWIN_OPTIONS.h"
7    
8     #ifdef ALLOW_PTRACERS
9     #ifdef ALLOW_DARWIN
10    
11     CStartOfInterFace
12     SUBROUTINE DARWIN_FIELDS_LOAD (
13     I myIter,myTime,myThid)
14    
15     C /==========================================================\
16     C | SUBROUTINE DARWIN_FIELDS_LOAD |
17     C | o Read in fields needed for ice fraction and |
18     C | iron aeolian flux terms, PAR and nut_wvel |
19     C | adapted from NPZD2Fe - Stephanie Dutkiewicz 2005 |
20     C |==========================================================|
21     IMPLICIT NONE
22    
23     C == GLobal variables ==
24     #include "SIZE.h"
25     #include "EEPARAMS.h"
26     #include "PARAMS.h"
27     #include "GRID.h"
28     #include "DARWIN_SIZE.h"
29     #include "SPECTRAL_SIZE.h"
30     #include "DARWIN_IO.h"
31     #include "DARWIN_FLUX.h"
32     c#include "GCHEM.h"
33     #ifdef ALLOW_SEAICE
34 jahn 1.5 #include "SEAICE_SIZE.h"
35 jahn 1.1 #include "SEAICE.h"
36     #endif
37     #ifdef ALLOW_THSICE
38     #include "THSICE_VARS.h"
39     #endif
40     #ifdef ALLOW_OFFLINE
41     #include "OFFLINE.h"
42     #endif
43     #ifdef OASIM
44     #include "SPECTRAL.h"
45     #endif
46    
47     C == Routine arguments ==
48     INTEGER myIter
49     _RL myTime
50     INTEGER myThid
51     C == Local variables ==
52     C msgBuf - Informational/error meesage buffer
53     CHARACTER*(MAX_LEN_MBUF) msgBuf
54     COMMON/ darwin_load /
55     & fice0, fice1, featmos0, featmos1, sur_par0, sur_par1
56     #ifdef ALLOW_CARBON
57     & ,dicwind0, dicwind1,atmosp0, atmosp1
58     #endif
59     #ifdef NUT_SUPPLY
60     & , nut_wvel0, nut_wvel1
61     #endif
62     #ifdef RELAX_NUTS
63     & , po4_obs0, po4_obs1, no3_obs0, no3_obs1
64     & , fet_obs0, fet_obs1, si_obs0, si_obs1
65     #endif
66     #ifdef FLUX_NUTS
67     & , po4_flx0, po4_flx1, no3_flx0, no3_flx1
68     & , fet_flx0, fet_flx1, si_flx0, si_flx1
69     #endif
70     #ifdef OASIM
71     & , oasim_ed0, oasim_ed1, oasim_es0, oasim_es1
72     #endif
73     _RS fice0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
74     _RS fice1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
75     _RS featmos0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
76     _RS featmos1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
77     _RS sur_par0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
78     _RS sur_par1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
79     #ifdef ALLOW_CARBON
80     _RS dicwind0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
81     _RS dicwind1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
82     _RS atmosp0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
83     _RS atmosp1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
84     #endif
85     #ifdef NUT_SUPPLY
86     _RS nut_wvel0 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
87     _RS nut_wvel1 (1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
88     #endif
89     #ifdef RELAX_NUTS
90     _RS po4_obs0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
91     _RS po4_obs1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
92     _RS no3_obs0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
93     _RS no3_obs1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
94     _RS fet_obs0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
95     _RS fet_obs1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
96     _RS si_obs0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
97     _RS si_obs1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
98     #endif
99     #ifdef FLUX_NUTS
100     _RS po4_flx0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
101     _RS po4_flx1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
102     _RS no3_flx0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
103     _RS no3_flx1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
104     _RS fet_flx0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
105     _RS fet_flx1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
106     _RS si_flx0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
107     _RS si_flx1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nR,nSx,nSy)
108     #endif
109     #ifdef OASIM
110     _RS oasim_ed0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,tlam,nSx,nSy)
111     _RS oasim_ed1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,tlam,nSx,nSy)
112     _RS oasim_es0(1-OLx:sNx+OLx,1-OLy:sNy+OLy,tlam,nSx,nSy)
113     _RS oasim_es1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,tlam,nSx,nSy)
114     _RS tmp1(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
115     _RS tmp2(1-OLx:sNx+OLx,1-OLy:sNy+OLy,nSx,nSy)
116     INTEGER ilam, fp, nj0, nj1
117     #endif
118     INTEGER bi,bj,i,j,k,intime0,intime1
119     _RL aWght,bWght,rdt
120     _RL tmp1Wght, tmp2Wght
121     INTEGER nForcingPeriods,Imytm,Ifprd,Ifcyc,Iftm
122     c
123     c
124     IF ( darwin_ForcingPeriod .NE. 0. _d 0 ) THEN
125    
126     C First call requires that we initialize everything to zero for safety
127     cQQQ need to check timing
128     IF ( myIter .EQ. nIter0 ) THEN
129     CALL LEF_ZERO( fice0,myThid )
130     CALL LEF_ZERO( fice1,myThid )
131     CALL LEF_ZERO( featmos0,myThid )
132     CALL LEF_ZERO( featmos1,myThid )
133     CALL LEF_ZERO( sur_par0,myThid )
134     CALL LEF_ZERO( sur_par1,myThid )
135     #ifdef ALLOW_CARBON
136     CALL LEF_ZERO( dicwind0,myThid )
137     CALL LEF_ZERO( dicwind1,myThid )
138     CALL LEF_ZERO( atmosp0,myThid )
139     CALL LEF_ZERO( atmosp1,myThid )
140     #endif
141     #ifdef NUT_SUPPLY
142     DO bj = myByLo(myThid), myByHi(myThid)
143     DO bi = myBxLo(myThid), myBxHi(myThid)
144     DO j=1-Oly,sNy+Oly
145     DO i=1-Olx,sNx+Olx
146     DO k=1,nR
147     nut_wvel0(i,j,k,bi,bj) = 0. _d 0
148     nut_wvel1(i,j,k,bi,bj) = 0. _d 0
149     ENDDO
150     ENDDO
151     ENDDO
152     ENDDO
153     ENDDO
154     #endif
155     #ifdef RELAX_NUTS
156     DO bj = myByLo(myThid), myByHi(myThid)
157     DO bi = myBxLo(myThid), myBxHi(myThid)
158     DO j=1-Oly,sNy+Oly
159     DO i=1-Olx,sNx+Olx
160     DO k=1,nR
161     po4_obs0(i,j,k,bi,bj) = 0. _d 0
162     po4_obs1(i,j,k,bi,bj) = 0. _d 0
163     no3_obs0(i,j,k,bi,bj) = 0. _d 0
164     no3_obs1(i,j,k,bi,bj) = 0. _d 0
165     fet_obs0(i,j,k,bi,bj) = 0. _d 0
166     fet_obs1(i,j,k,bi,bj) = 0. _d 0
167     si_obs0(i,j,k,bi,bj) = 0. _d 0
168     si_obs1(i,j,k,bi,bj) = 0. _d 0
169     ENDDO
170     ENDDO
171     ENDDO
172     ENDDO
173     ENDDO
174     #endif
175     #ifdef FLUX_NUTS
176     DO bj = myByLo(myThid), myByHi(myThid)
177     DO bi = myBxLo(myThid), myBxHi(myThid)
178     DO j=1-Oly,sNy+Oly
179     DO i=1-Olx,sNx+Olx
180     DO k=1,nR
181     po4_flx0(i,j,k,bi,bj) = 0. _d 0
182     po4_flx1(i,j,k,bi,bj) = 0. _d 0
183     no3_flx0(i,j,k,bi,bj) = 0. _d 0
184     no3_flx1(i,j,k,bi,bj) = 0. _d 0
185     fet_flx0(i,j,k,bi,bj) = 0. _d 0
186     fet_flx1(i,j,k,bi,bj) = 0. _d 0
187     si_flx0(i,j,k,bi,bj) = 0. _d 0
188     si_flx1(i,j,k,bi,bj) = 0. _d 0
189     ENDDO
190     ENDDO
191     ENDDO
192     ENDDO
193     ENDDO
194     #endif
195     #ifdef OASIM
196     DO bj = myByLo(myThid), myByHi(myThid)
197     DO bi = myBxLo(myThid), myBxHi(myThid)
198     DO j=1-Oly,sNy+Oly
199     DO i=1-Olx,sNx+Olx
200     tmp1(i,j,bi,bj) = 0. _d 0
201     tmp2(i,j,bi,bj) = 0. _d 0
202     DO ilam=1,tlam
203     oasim_ed0(i,j,ilam,bi,bj) = 0. _d 0
204     oasim_ed1(i,j,ilam,bi,bj) = 0. _d 0
205     oasim_es0(i,j,ilam,bi,bj) = 0. _d 0
206     oasim_es1(i,j,ilam,bi,bj) = 0. _d 0
207     ENDDO
208     ENDDO
209     ENDDO
210     ENDDO
211     ENDDO
212     #endif
213    
214    
215    
216     ENDIF
217    
218    
219     C Now calculate whether it is time to update the forcing arrays
220     rdt=1. _d 0 / deltaTclock
221     nForcingPeriods=
222     & int(darwin_ForcingCycle/darwin_ForcingPeriod+0.5 _d 0)
223     Imytm=int(myTime*rdt+0.5 _d 0)
224     Ifprd=int(darwin_ForcingPeriod*rdt+0.5 _d 0)
225     Ifcyc=int(darwin_ForcingCycle*rdt+0.5 _d 0)
226     Iftm=mod( Imytm+Ifcyc-Ifprd/2,Ifcyc)
227    
228     intime0=int(Iftm/Ifprd)
229     intime1=mod(intime0+1,nForcingPeriods)
230     tmp1Wght = FLOAT( Iftm-Ifprd*intime0 )
231     tmp2Wght = FLOAT( Ifprd )
232     aWght = tmp1Wght / tmp2Wght
233     bWght = 1. _d 0 - aWght
234    
235     intime0=intime0+1
236     intime1=intime1+1
237    
238    
239     cQQ something funny about timing here - need nIter0+1
240     c but seems okay for remaining timesteps
241     IF (
242     & Iftm-Ifprd*(intime0-1) .EQ. 0
243     & .OR. myIter .EQ. nIter0
244     & ) THEN
245    
246    
247     _BEGIN_MASTER(myThid)
248    
249     C If the above condition is met then we need to read in
250     C data for the period ahead and the period behind myTime.
251     WRITE(msgBuf,'(A,1P1E20.12,X,I10)')
252     & 'S/R DARWIN_FIELDS_LOAD: Reading forcing data',
253     & myTime,myIter
254     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
255     & SQUEEZE_RIGHT, myThid )
256    
257 jahn 1.4 _END_MASTER(myThid)
258    
259 jahn 1.7 _BARRIER
260    
261 jahn 1.1 IF ( darwin_iceFile .NE. ' ' ) THEN
262     CALL READ_REC_XY_RS( darwin_iceFile,fice0,intime0,
263     & myIter,myThid )
264     CALL READ_REC_XY_RS( darwin_IceFile,fice1,intime1,
265     & myIter,myThid )
266     ENDIF
267     IF ( darwin_ironFile .NE. ' ' ) THEN
268     CALL READ_REC_XY_RS( darwin_ironFile,featmos0,intime0,
269     & myIter,myThid )
270     CALL READ_REC_XY_RS( darwin_ironFile,featmos1,intime1,
271     & myIter,myThid )
272     ENDIF
273     IF ( darwin_PARFile .NE. ' ' ) THEN
274     CALL READ_REC_XY_RS( darwin_PARFile,sur_par0,intime0,
275     & myIter,myThid )
276     CALL READ_REC_XY_RS( darwin_PARFile,sur_par1,intime1,
277     & myIter,myThid )
278     ENDIF
279     #ifdef ALLOW_CARBON
280     IF ( DIC_windFile .NE. ' ' ) THEN
281     CALL READ_REC_XY_RS( DIC_windFile,dicwind0,intime0,
282     & myIter,myThid )
283     CALL READ_REC_XY_RS( DIC_windFile,dicwind1,intime1,
284     & myIter,myThid )
285     ENDIF
286     IF ( DIC_atmospFile .NE. ' ' ) THEN
287     CALL READ_REC_XY_RS( DIC_atmospFile,atmosp0,intime0,
288     & myIter,myThid )
289     CALL READ_REC_XY_RS( DIC_atmospFile,atmosp1,intime1,
290     & myIter,myThid )
291     ENDIF
292     #endif
293     #ifdef NUT_SUPPLY
294     IF ( darwin_nutWVelFile .NE. ' ' ) THEN
295     CALL READ_REC_XYZ_RS( darwin_nutWVelFile,nut_wvel0,intime0,
296     & myIter,myThid )
297     CALL READ_REC_XYZ_RS( darwin_nutWVelFile,nut_wvel1,intime1,
298     & myIter,myThid )
299     ENDIF
300     #endif
301     #ifdef RELAX_NUTS
302     IF ( darwin_PO4_RelaxFile .NE. ' ' ) THEN
303     CALL READ_REC_XYZ_RS( darwin_PO4_RelaxFile,po4_obs0,intime0,
304     & myIter,myThid )
305     CALL READ_REC_XYZ_RS( darwin_PO4_RelaxFile,po4_obs1,intime1,
306     & myIter,myThid )
307     ENDIF
308     IF ( darwin_NO3_RelaxFile .NE. ' ' ) THEN
309     CALL READ_REC_XYZ_RS( darwin_NO3_RelaxFile,no3_obs0,intime0,
310     & myIter,myThid )
311     CALL READ_REC_XYZ_RS( darwin_NO3_RelaxFile,no3_obs1,intime1,
312     & myIter,myThid )
313     ENDIF
314     IF ( darwin_Fet_RelaxFile .NE. ' ' ) THEN
315     CALL READ_REC_XYZ_RS( darwin_Fet_RelaxFile,fet_obs0,intime0,
316     & myIter,myThid )
317     CALL READ_REC_XYZ_RS( darwin_Fet_RelaxFile,fet_obs1,intime1,
318     & myIter,myThid )
319     ENDIF
320     IF ( darwin_Si_RelaxFile .NE. ' ' ) THEN
321     CALL READ_REC_XYZ_RS( darwin_Si_RelaxFile,si_obs0,intime0,
322     & myIter,myThid )
323     CALL READ_REC_XYZ_RS( darwin_Si_RelaxFile,si_obs1,intime1,
324     & myIter,myThid )
325     ENDIF
326     #endif
327     #ifdef FLUX_NUTS
328     IF ( darwin_PO4_FluxFile .NE. ' ' ) THEN
329     CALL READ_REC_XYZ_RS( darwin_PO4_FluxFile,po4_flx0,intime0,
330     & myIter,myThid )
331     CALL READ_REC_XYZ_RS( darwin_PO4_FluxFile,po4_flx1,intime1,
332     & myIter,myThid )
333     ENDIF
334     IF ( darwin_NO3_FluxFile .NE. ' ' ) THEN
335     CALL READ_REC_XYZ_RS( darwin_NO3_FluxFile,no3_flx0,intime0,
336     & myIter,myThid )
337     CALL READ_REC_XYZ_RS( darwin_NO3_FluxFile,no3_flx1,intime1,
338     & myIter,myThid )
339     ENDIF
340     IF ( darwin_Fet_FluxFile .NE. ' ' ) THEN
341     CALL READ_REC_XYZ_RS( darwin_Fet_FluxFile,fet_flx0,intime0,
342     & myIter,myThid )
343     CALL READ_REC_XYZ_RS( darwin_Fet_FluxFile,fet_flx1,intime1,
344     & myIter,myThid )
345     ENDIF
346     IF ( darwin_Si_FluxFile .NE. ' ' ) THEN
347     CALL READ_REC_XYZ_RS( darwin_Si_FluxFile,si_flx0,intime0,
348     & myIter,myThid )
349     CALL READ_REC_XYZ_RS( darwin_Si_FluxFile,si_flx1,intime1,
350     & myIter,myThid )
351     ENDIF
352     #endif
353     #ifdef OASIM
354     IF ( darwin_oasim_edFile .NE. ' ' ) THEN
355     nj0= (intime0-1)*tlam
356     nj1= (intime1-1)*tlam
357     c print*,'ZZ nj0,nj1',nj0, nj1, intime0, intime1
358     do ilam=1,tlam
359     nj0=nj0+1
360     CALL READ_REC_XY_RS( darwin_oasim_edFile, tmp1,nj0,
361     & myIter,myThid )
362     nj1=nj1+1
363     CALL READ_REC_XY_RS( darwin_oasim_edFile, tmp2,nj1,
364     & myIter,myThid )
365     DO bj = myByLo(myThid), myByHi(myThid)
366     DO bi = myBxLo(myThid), myBxHi(myThid)
367     DO j=1-Oly,sNy+Oly
368     DO i=1-Olx,sNx+Olx
369     oasim_ed0(i,j,ilam,bi,bj) = tmp1(i,j,bi,bj)
370     oasim_ed1(i,j,ilam,bi,bj) = tmp2(i,j,bi,bj)
371     ENDDO
372     ENDDO
373     ENDDO
374     ENDDO
375     c print*,oasim_ed0(1,1,ilam,1,1), oasim_ed1(1,1,ilam,1,1)
376     enddo
377     c CALL READ_MFLDS_3D_RS( darwin_oasim_edFile, oasim_ed0,
378     c & nj0, fp, tlam, myIter,myThid )
379     c CALL READ_MFLDS_3D_RS( darwin_oasim_edFile, oasim_ed1,
380     c & nj1, fp, tlam, myIter,myThid )
381     ENDIF
382     IF ( darwin_oasim_esFile .NE. ' ' ) THEN
383     nj0= (intime0-1)*tlam
384     nj1= (intime1-1)*tlam
385     do ilam=1,tlam
386     nj0=nj0+1
387     CALL READ_REC_XY_RS( darwin_oasim_esFile, tmp1,nj0,
388     & myIter,myThid )
389     nj1=nj1+1
390     CALL READ_REC_XY_RS( darwin_oasim_esFile, tmp2,nj1,
391     & myIter,myThid )
392     DO bj = myByLo(myThid), myByHi(myThid)
393     DO bi = myBxLo(myThid), myBxHi(myThid)
394     DO j=1-Oly,sNy+Oly
395     DO i=1-Olx,sNx+Olx
396     oasim_es0(i,j,ilam,bi,bj) = tmp1(i,j,bi,bj)
397     oasim_es1(i,j,ilam,bi,bj) = tmp2(i,j,bi,bj)
398     ENDDO
399     ENDDO
400     ENDDO
401     ENDDO
402     enddo
403     c CALL READ_MFLDS_3D_RS( darwin_oasim_esFile, oasim_es0,
404     c & nj0, fp, tlam, myIter,myThid )
405     c CALL READ_MFLDS_3D_RS( darwin_oasim_esFile, oasim_es1,
406     c & nj1, fp, tlam, myIter,myThid )
407     ENDIF
408     #endif
409     C
410     _EXCH_XY_RS(fice0, myThid )
411     _EXCH_XY_RS(fice1, myThid )
412     _EXCH_XY_RS(featmos0, myThid )
413     _EXCH_XY_RS(featmos1, myThid )
414     _EXCH_XY_RS(sur_par0, myThid )
415     _EXCH_XY_RS(sur_par1, myThid )
416     #ifdef ALLOW_CARBON
417     _EXCH_XY_RS(dicwind0, myThid )
418     _EXCH_XY_RS(dicwind1, myThid )
419     _EXCH_XY_RS(atmosp0, myThid )
420     _EXCH_XY_RS(atmosp1, myThid )
421     #endif
422     #ifdef NUT_SUPPLY
423     _EXCH_XYZ_RS(nut_wvel0, myThid )
424     _EXCH_XYZ_RS(nut_wvel1, myThid )
425     #endif
426     #ifdef RELAX_NUTS
427     _EXCH_XYZ_RS(po4_obs0, myThid )
428     _EXCH_XYZ_RS(po4_obs1, myThid )
429     _EXCH_XYZ_RS(no3_obs0, myThid )
430     _EXCH_XYZ_RS(no3_obs1, myThid )
431     _EXCH_XYZ_RS(fet_obs0, myThid )
432     _EXCH_XYZ_RS(fet_obs1, myThid )
433     _EXCH_XYZ_RS(si_obs0, myThid )
434     _EXCH_XYZ_RS(si_obs1, myThid )
435     #endif
436     #ifdef FLUX_NUTS
437     _EXCH_XYZ_RS(po4_flx0, myThid )
438     _EXCH_XYZ_RS(po4_flx1, myThid )
439     _EXCH_XYZ_RS(no3_flx0, myThid )
440     _EXCH_XYZ_RS(no3_flx1, myThid )
441     _EXCH_XYZ_RS(fet_flx0, myThid )
442     _EXCH_XYZ_RS(fet_flx1, myThid )
443     _EXCH_XYZ_RS(si_flx0, myThid )
444     _EXCH_XYZ_RS(si_flx1, myThid )
445     #endif
446     #ifdef OASIM
447     CALL EXCH_3D_RS (oasim_ed0, tlam, myThid)
448     CALL EXCH_3D_RS (oasim_ed1, tlam, myThid)
449     CALL EXCH_3D_RS (oasim_es0, tlam, myThid)
450 jahn 1.6 CALL EXCH_3D_RS (oasim_es1, tlam, myThid)
451 jahn 1.1 #endif
452    
453    
454     C
455     ENDIF
456    
457     DO bj = myByLo(myThid), myByHi(myThid)
458     DO bi = myBxLo(myThid), myBxHi(myThid)
459     DO j=1-Oly,sNy+Oly
460     DO i=1-Olx,sNx+Olx
461     cQQ need to include ice model here, if used
462     #ifdef ALLOW_THSICE
463     FIce(i,j,bi,bj) = iceMask(i,j,bi,bj)
464     #else
465     #ifdef ALLOW_SEAICE
466     FIce(i,j,bi,bj) = AREA(i,j,bi,bj)
467     #else
468     IF ( darwin_iceFile .NE. ' ' ) THEN
469     fice(i,j,bi,bj) = bWght*fice0(i,j,bi,bj)
470     & +aWght*fice1(i,j,bi,bj)
471     ELSE
472     fice(i,j,bi,bj) = 0. _d 0
473     ENDIF
474     #endif
475     #endif
476     c or use offline fields if provided
477     #ifdef ALLOW_OFFLINE
478     IF (IceFile .NE. ' ') THEN
479     fice(i,j,bi,bj) = ICEM(i,j,bi,bj)
480     ENDIF
481     #endif
482    
483     IF ( darwin_ironFile .NE. ' ' ) THEN
484     inputFe(i,j,bi,bj) = bWght*featmos0(i,j,bi,bj)
485     & +aWght*featmos1(i,j,bi,bj)
486     c convert to mmol/m2/s
487 jahn 1.3 inputFe(i,j,bi,bj) = inputFe(i,j,bi,bj)*darwin_ironFileConv
488 jahn 1.1 ELSE
489     inputFe(i,j,bi,bj) = 0. _d 0
490     ENDIF
491 jahn 1.2 c light
492 jahn 1.1 IF ( darwin_PARFile .NE. ' ' ) THEN
493     sur_par(i,j,bi,bj) = bWght*sur_par0(i,j,bi,bj)
494     & +aWght*sur_par1(i,j,bi,bj)
495 jahn 1.2 c convert to uEin/m2/s
496     sur_par(i,j,bi,bj) = sur_par(i,j,bi,bj)*darwin_PARFileConv
497 jahn 1.1 ELSE
498     sur_par(i,j,bi,bj) = 200. _d 0*maskC(i,j,1,bi,bj)
499     ENDIF
500     #ifdef ALLOW_CARBON
501     IF ( DIC_windFile .NE. ' ' ) THEN
502     WIND(i,j,bi,bj) = bWght*dicwind0(i,j,bi,bj)
503     & + aWght*dicwind1(i,j,bi,bj)
504     ELSE
505     WIND(i,j,bi,bj) = 5. _d 0
506     ENDIF
507     #ifndef USE_PLOAD
508     IF ( DIC_atmospFile .NE. ' ' ) THEN
509     AtmosP(i,j,bi,bj) = bWght*atmosp0(i,j,bi,bj)
510     & + aWght*atmosp1(i,j,bi,bj)
511     ELSE
512     AtmosP(i,j,bi,bj) = 1. _d 0
513     ENDIF
514     #endif
515     #endif
516     #ifdef NUT_SUPPLY
517     c artificial wvel for nutrient supply in 1-d and 2-d models
518     IF ( darwin_nutWVelFile .NE. ' ' ) THEN
519     DO k=1,nR
520     nut_wvel(i,j,k,bi,bj) = bWght*nut_wvel0(i,j,k,bi,bj)
521     & +aWght*nut_wvel1(i,j,k,bi,bj)
522     ENDDO
523     ENDIF
524     #endif
525     #ifdef RELAX_NUTS
526     IF ( darwin_PO4_RelaxFile .NE. ' ' ) THEN
527     DO k=1,nR
528     po4_obs(i,j,k,bi,bj) = bWght*po4_obs0(i,j,k,bi,bj)
529     & +aWght*po4_obs1(i,j,k,bi,bj)
530     ENDDO
531     ENDIF
532     IF ( darwin_NO3_RelaxFile .NE. ' ' ) THEN
533     DO k=1,nR
534     no3_obs(i,j,k,bi,bj) = bWght*no3_obs0(i,j,k,bi,bj)
535     & +aWght*no3_obs1(i,j,k,bi,bj)
536     ENDDO
537     ENDIF
538     IF ( darwin_Fet_RelaxFile .NE. ' ' ) THEN
539     DO k=1,nR
540     fet_obs(i,j,k,bi,bj) = bWght*fet_obs0(i,j,k,bi,bj)
541     & +aWght*fet_obs1(i,j,k,bi,bj)
542     ENDDO
543     ENDIF
544     IF ( darwin_Si_RelaxFile .NE. ' ' ) THEN
545     DO k=1,nR
546     si_obs(i,j,k,bi,bj) = bWght*si_obs0(i,j,k,bi,bj)
547     & +aWght*si_obs1(i,j,k,bi,bj)
548     ENDDO
549     ENDIF
550     #endif
551     #ifdef FLUX_NUTS
552     IF ( darwin_PO4_FluxFile .NE. ' ' ) THEN
553     DO k=1,nR
554     po4_flx(i,j,k,bi,bj) = bWght*po4_flx0(i,j,k,bi,bj)
555     & +aWght*po4_flx1(i,j,k,bi,bj)
556     ENDDO
557     ENDIF
558     IF ( darwin_NO3_FluxFile .NE. ' ' ) THEN
559     DO k=1,nR
560     no3_flx(i,j,k,bi,bj) = bWght*no3_flx0(i,j,k,bi,bj)
561     & +aWght*no3_flx1(i,j,k,bi,bj)
562     ENDDO
563     ENDIF
564     IF ( darwin_Fet_FluxFile .NE. ' ' ) THEN
565     DO k=1,nR
566     fet_flx(i,j,k,bi,bj) = bWght*fet_flx0(i,j,k,bi,bj)
567     & +aWght*fet_flx1(i,j,k,bi,bj)
568     ENDDO
569     ENDIF
570     IF ( darwin_Si_FluxFile .NE. ' ' ) THEN
571     DO k=1,nR
572     si_flx(i,j,k,bi,bj) = bWght*si_flx0(i,j,k,bi,bj)
573     & +aWght*si_flx1(i,j,k,bi,bj)
574     ENDDO
575     ENDIF
576     #endif
577     #ifdef OASIM
578     IF ( darwin_oasim_edFile .NE. ' ' ) THEN
579     c oasim data (load as W/m2 per band)
580     DO ilam=1,tlam
581     oasim_ed(i,j,ilam,bi,bj) =
582     & bWght*oasim_ed0(i,j,ilam,bi,bj)
583     & +aWght*oasim_ed1(i,j,ilam,bi,bj)
584     c oasim_ed(i,j,ilam,bi,bj) =
585     c & oasim_ed(i,j,ilam,bi,bj)*1. _d 6/86400. _d 0
586     ENDDO
587     ENDIF
588     IF ( darwin_oasim_esFile .NE. ' ' ) THEN
589     DO ilam=1,tlam
590     oasim_es(i,j,ilam,bi,bj) =
591     & bWght*oasim_es0(i,j,ilam,bi,bj)
592     & +aWght*oasim_es1(i,j,ilam,bi,bj)
593     c oasim_es(i,j,ilam,bi,bj) =
594     c & oasim_es(i,j,ilam,bi,bj)*1. _d 6/86400. _d 0
595     ENDDO
596     ENDIF
597     #ifndef WAVEBANDS
598     c if not spectral add wavebands to give a single surface PAR
599     c and convert to uEin/m2/s
600     sur_par(i,j,bi,bj)= 0. _d 0
601     DO ilam=1,tlam
602     sur_par(i,j,bi,bj)=sur_par(i,j,bi,bj)+WtouEins(ilam)
603     & *(oasim_ed(i,j,ilam,bi,bj)+
604     & oasim_es(i,j,ilam,bi,bj))
605     ENDDO
606     #endif
607     #endif
608     c
609     ENDDO
610     ENDDO
611     ENDDO
612     ENDDO
613    
614     C endif for periodicForcing
615     ENDIF
616    
617     RETURN
618     END
619     #endif
620     #endif
621    

  ViewVC Help
Powered by ViewVC 1.1.22