/[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.4 - (hide annotations) (download)
Wed Dec 7 20:04:00 2011 UTC (13 years, 7 months ago) by jahn
Branch: MAIN
CVS Tags: ctrb_darwin2_ckpt63i_20120124, ctrb_darwin2_ckpt63j_20120217, ctrb_darwin2_ckpt63g_20111220, ctrb_darwin2_ckpt63h_20111230
Changes since 1.3: +3 -3 lines
fix some multi-threading bits

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

  ViewVC Help
Powered by ViewVC 1.1.22