/[MITgcm]/MITgcm_contrib/ecco_darwin/v3_cs510_Brix/code/exf_getffields.F
ViewVC logotype

Annotation of /MITgcm_contrib/ecco_darwin/v3_cs510_Brix/code/exf_getffields.F

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


Revision 1.1 - (hide annotations) (download)
Tue Nov 28 19:50:42 2017 UTC (7 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
Holger Brix's ECCO-Darwin version 3 with circa-2011 MITgcm

1 dimitri 1.1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_getffields.F,v 1.43 2010/07/13 00:02:10 gforget Exp $
2     C $Name: $
3    
4     #include "EXF_OPTIONS.h"
5    
6     subroutine exf_getffields( mytime, myiter, mythid )
7    
8     c ==================================================================
9     c SUBROUTINE exf_getffields
10     c ==================================================================
11     c
12     c o Read-in atmospheric state and/or surface fluxes from files.
13     c
14     c heimbach@mit.edu, 23-May-2003 totally re-structured
15     c 5-Aug-2003: added USE_EXF_INTERPOLATION for arbitrary input grid
16     c
17     c ==================================================================
18     c SUBROUTINE exf_getffields
19     c ==================================================================
20    
21     implicit none
22    
23     c == global variables ==
24    
25     #include "EEPARAMS.h"
26     #include "SIZE.h"
27     #include "PARAMS.h"
28     #include "DYNVARS.h"
29     #include "GRID.h"
30    
31     #include "EXF_PARAM.h"
32     #include "EXF_FIELDS.h"
33     #include "EXF_CONSTANTS.h"
34    
35     #ifdef ALLOW_AUTODIFF
36     # include "ctrl.h"
37     # include "ctrl_dummy.h"
38     #endif
39    
40     c == routine arguments ==
41    
42     integer mythid
43     integer myiter
44     _RL mytime
45    
46     c == local variables ==
47    
48     integer i, j, bi, bj, interp_method
49     parameter(interp_method=1)
50    
51     #ifdef ALLOW_ROTATE_UV_CONTROLS
52     _RL tmpUE(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
53     _RL tmpVN(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
54     _RL tmpUX(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
55     _RL tmpVY(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
56     #endif
57    
58     c == end of interface ==
59    
60     c-- read forcing fields from files and temporal interpolation
61    
62     c Zonal and meridional wind stress.
63     #ifdef USE_EXF_INTERPOLATION
64     call exf_set_uv(
65     & ustressfile, ustressstartdate, ustressperiod,
66     & exf_inscal_ustress, ustress, ustress0, ustress1, ustressmask,
67     & ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
68     & ustress_nlon, ustress_nlat,
69     & ustress_exfremo_intercept, ustress_exfremo_slope,
70     & vstressfile, vstressstartdate, vstressperiod,
71     & exf_inscal_vstress, vstress, vstress0, vstress1, vstressmask,
72     & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
73     & vstress_nlon, vstress_nlat,
74     & vstress_exfremo_intercept, vstress_exfremo_slope,
75     & mytime, myiter, mythid )
76     #else /* ifndef USE_EXF_INTERPOLATION */
77     call exf_set_gen(
78     & ustressfile, ustressstartdate, ustressperiod,
79     & exf_inscal_ustress,
80     & ustress_exfremo_intercept, ustress_exfremo_slope,
81     & ustress, ustress0, ustress1, ustressmask,
82     & mytime, myiter, mythid )
83     call exf_set_gen(
84     & vstressfile, vstressstartdate, vstressperiod,
85     & exf_inscal_vstress,
86     & vstress_exfremo_intercept, vstress_exfremo_slope,
87     & vstress, vstress0, vstress1, vstressmask,
88     & mytime, myiter, mythid )
89     #endif /* USE_EXF_INTERPOLATION */
90    
91     c-- wind speed
92     call exf_set_gen(
93     & wspeedfile, wspeedstartdate, wspeedperiod,
94     & exf_inscal_wspeed,
95     & wspeed_exfremo_intercept, wspeed_exfremo_slope,
96     & wspeed, wspeed0, wspeed1, wspeedmask,
97     #ifdef USE_EXF_INTERPOLATION
98     & wspeed_lon0, wspeed_lon_inc,
99     & wspeed_lat0, wspeed_lat_inc,
100     & wspeed_nlon, wspeed_nlat, xC, yC, interp_method,
101     #endif
102     & mytime, myiter, mythid )
103    
104     #ifdef ALLOW_ATM_WIND
105    
106     c Zonal and meridional wind.
107     #ifdef USE_EXF_INTERPOLATION
108     call exf_set_uv(
109     & uwindfile, uwindstartdate, uwindperiod,
110     & exf_inscal_uwind, uwind, uwind0, uwind1, uwindmask,
111     & uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
112     & uwind_nlon, uwind_nlat,
113     & uwind_exfremo_intercept, uwind_exfremo_slope,
114     & vwindfile, vwindstartdate, vwindperiod,
115     & exf_inscal_vwind, vwind, vwind0, vwind1, vwindmask,
116     & vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
117     & vwind_nlon, vwind_nlat,
118     & vwind_exfremo_intercept, vwind_exfremo_slope,
119     & mytime, myiter, mythid )
120     #else /* ifndef USE_EXF_INTERPOLATION */
121     call exf_set_gen(
122     & uwindfile, uwindstartdate, uwindperiod,
123     & exf_inscal_uwind,
124     & uwind_exfremo_intercept, uwind_exfremo_slope,
125     & uwind, uwind0, uwind1, uwindmask,
126     & mytime, myiter, mythid )
127     call exf_set_gen(
128     & vwindfile, vwindstartdate, vwindperiod,
129     & exf_inscal_vwind,
130     & vwind_exfremo_intercept, vwind_exfremo_slope,
131     & vwind, vwind0, vwind1, vwindmask,
132     & mytime, myiter, mythid )
133     #endif /* USE_EXF_INTERPOLATION */
134    
135     if (useRelativeWind) then
136     C Subtract UVEL and VVEL from UWIND and VWIND.
137     do bj = mybylo(mythid),mybyhi(mythid)
138     do bi = mybxlo(mythid),mybxhi(mythid)
139     do j = 1,sny
140     do i = 1,snx
141     uwind(i,j,bi,bj) = uwind(i,j,bi,bj) - 0.5 _d 0 *
142     & (uVel(i,j,1,bi,bj)+uVel(i+1,j,1,bi,bj))
143     vwind(i,j,bi,bj) = vwind(i,j,bi,bj) - 0.5 _d 0 *
144     & (vVel(i,j,1,bi,bj)+vVel(i,j+1,1,bi,bj))
145     enddo
146     enddo
147     enddo
148     enddo
149     endif
150    
151     #endif /* ALLOW_ATM_WIND */
152    
153     c Atmospheric heat flux.
154     call exf_set_gen (
155     & hfluxfile, hfluxstartdate, hfluxperiod,
156     & exf_inscal_hflux,
157     & hflux_exfremo_intercept, hflux_exfremo_slope,
158     & hflux, hflux0, hflux1, hfluxmask,
159     #ifdef USE_EXF_INTERPOLATION
160     & hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
161     & hflux_nlon, hflux_nlat, xC, yC, interp_method,
162     #endif
163     & mytime, myiter, mythid )
164    
165     c Salt flux.
166     call exf_set_gen (
167     & sfluxfile, sfluxstartdate, sfluxperiod,
168     & exf_inscal_sflux,
169     & sflux_exfremo_intercept, sflux_exfremo_slope,
170     & sflux, sflux0, sflux1, sfluxmask,
171     #ifdef USE_EXF_INTERPOLATION
172     & sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
173     & sflux_nlon, sflux_nlat, xC, yC, interp_method,
174     #endif
175     & mytime, myiter, mythid )
176    
177     #ifdef ALLOW_ATM_TEMP
178    
179     c Atmospheric temperature.
180     call exf_set_gen(
181     & atempfile, atempstartdate, atempperiod,
182     & exf_inscal_atemp,
183     & atemp_exfremo_intercept, atemp_exfremo_slope,
184     & atemp, atemp0, atemp1, atempmask,
185     #ifdef USE_EXF_INTERPOLATION
186     & atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
187     & atemp_nlon, atemp_nlat, xC, yC, interp_method,
188     #endif
189     & mytime, myiter, mythid )
190     do bj = mybylo(mythid),mybyhi(mythid)
191     do bi = mybxlo(mythid),mybxhi(mythid)
192     do j = 1,sny
193     do i = 1,snx
194     atemp(i,j,bi,bj) = atemp(i,j,bi,bj) + exf_offset_atemp
195     enddo
196     enddo
197     enddo
198     enddo
199    
200     c Atmospheric humidity.
201     call exf_set_gen(
202     & aqhfile, aqhstartdate, aqhperiod,
203     & exf_inscal_aqh,
204     & aqh_exfremo_intercept, aqh_exfremo_slope,
205     & aqh, aqh0, aqh1, aqhmask,
206     #ifdef USE_EXF_INTERPOLATION
207     & aqh_lon0, aqh_lon_inc, aqh_lat0, aqh_lat_inc,
208     & aqh_nlon, aqh_nlat, xC, yC, interp_method,
209     #endif
210     & mytime, myiter, mythid )
211    
212     c Net long wave radiative flux.
213     call exf_set_gen(
214     & lwfluxfile, lwfluxstartdate, lwfluxperiod,
215     & exf_inscal_lwflux,
216     & lwflux_exfremo_intercept, lwflux_exfremo_slope,
217     & lwflux, lwflux0, lwflux1, lwfluxmask,
218     #ifdef USE_EXF_INTERPOLATION
219     & lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
220     & lwflux_nlon, lwflux_nlat, xC, yC, interp_method,
221     #endif
222     & mytime, myiter, mythid )
223    
224     c Precipitation.
225     call exf_set_gen(
226     & precipfile, precipstartdate, precipperiod,
227     & exf_inscal_precip,
228     & precip_exfremo_intercept, precip_exfremo_slope,
229     & precip, precip0, precip1, precipmask,
230     #ifdef USE_EXF_INTERPOLATION
231     & precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
232     & precip_nlon, precip_nlat, xC, yC, interp_method,
233     #endif
234     & mytime, myiter, mythid )
235    
236     c Snow.
237     call exf_set_gen(
238     & snowprecipfile, snowprecipstartdate, snowprecipperiod,
239     & exf_inscal_snowprecip,
240     & snowprecip_exfremo_intercept, snowprecip_exfremo_slope,
241     & snowprecip, snowprecip0, snowprecip1, snowprecipmask,
242     #ifdef USE_EXF_INTERPOLATION
243     & snowprecip_lon0, snowprecip_lon_inc,
244     & snowprecip_lat0, snowprecip_lat_inc,
245     & snowprecip_nlon, snowprecip_nlat, xC, yC, interp_method,
246     #endif
247     & mytime, myiter, mythid )
248    
249     #endif /* ALLOW_ATM_TEMP */
250    
251     #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
252     c Net short wave radiative flux.
253     call exf_set_gen (
254     & swfluxfile, swfluxstartdate, swfluxperiod,
255     & exf_inscal_swflux,
256     & swflux_exfremo_intercept, swflux_exfremo_slope,
257     & swflux, swflux0, swflux1, swfluxmask,
258     #ifdef USE_EXF_INTERPOLATION
259     & swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
260     & swflux_nlon, swflux_nlat, xC, yC, interp_method,
261     #endif
262     & mytime, myiter, mythid )
263     #endif
264    
265     #ifdef EXF_READ_EVAP
266     c Evaporation
267     call exf_set_gen (
268     & evapfile, evapstartdate, evapperiod,
269     & exf_inscal_evap,
270     & evap_exfremo_intercept, evap_exfremo_slope,
271     & evap, evap0, evap1, evapmask,
272     #ifdef USE_EXF_INTERPOLATION
273     & evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
274     & evap_nlon, evap_nlat, xC, yC, interp_method,
275     #endif
276     & mytime, myiter, mythid )
277     #endif
278    
279     #ifdef ALLOW_DOWNWARD_RADIATION
280    
281     c Downward shortwave radiation.
282     call exf_set_gen (
283     & swdownfile, swdownstartdate, swdownperiod,
284     & exf_inscal_swdown,
285     & swdown_exfremo_intercept, swdown_exfremo_slope,
286     & swdown, swdown0, swdown1, swdownmask,
287     #ifdef USE_EXF_INTERPOLATION
288     & swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
289     & swdown_nlon, swdown_nlat, xC, yC, interp_method,
290     #endif
291     & mytime, myiter, mythid )
292    
293     c Downward longwave radiation.
294     call exf_set_gen (
295     & lwdownfile, lwdownstartdate, lwdownperiod,
296     & exf_inscal_lwdown,
297     & lwdown_exfremo_intercept, lwdown_exfremo_slope,
298     & lwdown, lwdown0, lwdown1, lwdownmask,
299     #ifdef USE_EXF_INTERPOLATION
300     & lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
301     & lwdown_nlon, lwdown_nlat, xC, yC, interp_method,
302     #endif
303     & mytime, myiter, mythid )
304    
305     #endif
306    
307     #ifdef ATMOSPHERIC_LOADING
308     c Atmos. pressure forcing
309     call exf_set_gen (
310     & apressurefile, apressurestartdate, apressureperiod,
311     & exf_inscal_apressure,
312     & apressure_exfremo_intercept, apressure_exfremo_slope,
313     & apressure, apressure0, apressure1, apressuremask,
314     #ifdef USE_EXF_INTERPOLATION
315     & apressure_lon0, apressure_lon_inc, apressure_lat0,
316     & apressure_lat_inc, apressure_nlon, apressure_nlat, xC, yC,
317     & interp_method,
318     #endif
319     & mytime, myiter, mythid )
320     #endif
321    
322     #ifdef ALLOW_ICE_AREAMASK
323     c fractional ice-covered area MASK
324     call exf_set_gen (
325     & areamaskfile, areamaskstartdate, areamaskperiod,
326     & exf_inscal_areamask,
327     & areamask_exfremo_intercept, areamask_exfremo_slope,
328     & areamask, areamask0, areamask1, areamaskmask,
329     #ifdef USE_EXF_INTERPOLATION
330     & areamask_lon0, areamask_lon_inc, areamask_lat0,
331     & areamask_lat_inc, areamask_nlon, areamask_nlat, xC, yC,
332     & interp_method,
333     #endif
334     & mytime, myiter, mythid )
335     #endif
336    
337     #ifdef ALLOW_RUNOFF
338     c Runoff
339     #ifdef USE_NO_INTERP_RUNOFF
340     call exf_set_runoff (
341     & runofffile, runoffstartdate, runoffperiod,
342     & exf_inscal_runoff,
343     & runoff_exfremo_intercept, runoff_exfremo_slope,
344     & runoff, runoff0, runoff1, runoffmask,
345     & mytime, myiter, mythid )
346     #else /* ndef USE_NO_INTERP_RUNOFF */
347     call exf_set_gen (
348     & runofffile, runoffstartdate, runoffperiod,
349     & exf_inscal_runoff,
350     & runoff_exfremo_intercept, runoff_exfremo_slope,
351     & runoff, runoff0, runoff1, runoffmask,
352     #ifdef USE_EXF_INTERPOLATION
353     & runoff_lon0, runoff_lon_inc, runoff_lat0,
354     & runoff_lat_inc, runoff_nlon, runoff_nlat, xC, yC,
355     & interp_method,
356     #endif
357     & mytime, myiter, mythid )
358     #endif /* def USE_NO_INTERP_RUNOFF */
359     #endif
360    
361     c-- Control variables for atmos. state
362    
363     #ifdef ALLOW_ATEMP_CONTROL
364     call ctrl_get_gen (
365     & xx_atemp_file, xx_atempstartdate, xx_atempperiod,
366     & maskc, atemp, xx_atemp0, xx_atemp1, xx_atemp_dummy,
367     & xx_atemp_remo_intercept, xx_atemp_remo_slope,
368     & mytime, myiter, mythid )
369     #endif
370    
371     #ifdef ALLOW_AQH_CONTROL
372     call ctrl_get_gen (
373     & xx_aqh_file, xx_aqhstartdate, xx_aqhperiod,
374     & maskc, aqh, xx_aqh0, xx_aqh1, xx_aqh_dummy,
375     & xx_aqh_remo_intercept, xx_aqh_remo_slope,
376     & mytime, myiter, mythid )
377     #endif
378    
379     #ifdef ALLOW_PRECIP_CONTROL
380     call ctrl_get_gen (
381     & xx_precip_file, xx_precipstartdate, xx_precipperiod,
382     & maskc, precip, xx_precip0, xx_precip1, xx_precip_dummy,
383     & xx_precip_remo_intercept, xx_precip_remo_slope,
384     & mytime, myiter, mythid )
385     #endif
386    
387     #ifdef ALLOW_SWFLUX_CONTROL
388     call ctrl_get_gen (
389     & xx_swflux_file, xx_swfluxstartdate, xx_swfluxperiod,
390     & maskc, swflux, xx_swflux0, xx_swflux1, xx_swflux_dummy,
391     & xx_swflux_remo_intercept, xx_swflux_remo_slope,
392     & mytime, myiter, mythid )
393     #endif
394    
395     #ifdef ALLOW_SWDOWN_CONTROL
396     call ctrl_get_gen (
397     & xx_swdown_file, xx_swdownstartdate, xx_swdownperiod,
398     & maskc, swdown, xx_swdown0, xx_swdown1, xx_swdown_dummy,
399     & xx_swdown_remo_intercept, xx_swdown_remo_slope,
400     & mytime, myiter, mythid )
401     #endif
402    
403     #ifdef ALLOW_LWFLUX_CONTROL
404     call ctrl_get_gen (
405     & xx_lwflux_file, xx_lwfluxstartdate, xx_lwfluxperiod,
406     & maskc, lwflux, xx_lwflux0, xx_lwflux1, xx_lwflux_dummy,
407     & xx_lwflux_remo_intercept, xx_lwflux_remo_slope,
408     & mytime, myiter, mythid )
409     #endif
410    
411     #ifdef ALLOW_LWDOWN_CONTROL
412     call ctrl_get_gen (
413     & xx_lwdown_file, xx_lwdownstartdate, xx_lwdownperiod,
414     & maskc, lwdown, xx_lwdown0, xx_lwdown1, xx_lwdown_dummy,
415     & xx_lwdown_remo_intercept, xx_lwdown_remo_slope,
416     & mytime, myiter, mythid )
417     #endif
418    
419     #ifdef ALLOW_EVAP_CONTROL
420     call ctrl_get_gen (
421     & xx_evap_file, xx_evapstartdate, xx_evapperiod,
422     & maskc, evap, xx_evap0, xx_evap1, xx_evap_dummy,
423     & xx_evap_remo_intercept, xx_evap_remo_slope,
424     & mytime, myiter, mythid )
425     #endif
426    
427     #ifdef ALLOW_SNOWPRECIP_CONTROL
428     call ctrl_get_gen (
429     & xx_snowprecip_file, xx_snowprecipstartdate,
430     & xx_snowprecipperiod,
431     & maskc, snowprecip, xx_snowprecip0, xx_snowprecip1,
432     & xx_snowprecip_dummy,
433     & xx_snowprecip_remo_intercept, xx_snowprecip_remo_slope,
434     & mytime, myiter, mythid )
435     #endif
436    
437     #ifdef ALLOW_APRESSURE_CONTROL
438     call ctrl_get_gen (
439     & xx_apressure_file, xx_apressurestartdate,
440     & xx_apressureperiod,
441     & maskc, apressure, xx_apressure0, xx_apressure1,
442     & xx_apressure_dummy,
443     & xx_apressure_remo_intercept, xx_apressure_remo_slope,
444     & mytime, myiter, mythid )
445     #endif
446    
447     #ifndef ALLOW_ROTATE_UV_CONTROLS
448    
449     #ifdef ALLOW_UWIND_CONTROL
450     call ctrl_get_gen (
451     & xx_uwind_file, xx_uwindstartdate, xx_uwindperiod,
452     & maskc, uwind, xx_uwind0, xx_uwind1, xx_uwind_dummy,
453     & xx_uwind_remo_intercept, xx_uwind_remo_slope,
454     & mytime, myiter, mythid )
455     #endif /* ALLOW_UWIND_CONTROL */
456    
457     #ifdef ALLOW_VWIND_CONTROL
458     call ctrl_get_gen (
459     & xx_vwind_file, xx_vwindstartdate, xx_vwindperiod,
460     & maskc, vwind, xx_vwind0, xx_vwind1, xx_vwind_dummy,
461     & xx_vwind_remo_intercept, xx_vwind_remo_slope,
462     & mytime, myiter, mythid )
463     #endif /* ALLOW_VWIND_CONTROL */
464    
465     #else
466    
467     #if defined(ALLOW_UWIND_CONTROL) && defined(ALLOW_VWIND_CONTROL)
468    
469     do bj = mybylo(mythid),mybyhi(mythid)
470     do bi = mybxlo(mythid),mybxhi(mythid)
471     do j = 1-oly,sny+oly
472     do i = 1-olx,snx+olx
473     tmpUE(i,j,bi,bj) = 0. _d 0
474     tmpVN(i,j,bi,bj) = 0. _d 0
475     tmpUX(i,j,bi,bj) = 0. _d 0
476     tmpVY(i,j,bi,bj) = 0. _d 0
477     enddo
478     enddo
479     enddo
480     enddo
481    
482     call ctrl_get_gen (
483     & xx_uwind_file, xx_uwindstartdate, xx_uwindperiod,
484     & maskc, tmpUE, xx_uwind0, xx_uwind1, xx_uwind_dummy,
485     & xx_uwind_remo_intercept, xx_uwind_remo_slope,
486     & mytime, myiter, mythid )
487    
488     call ctrl_get_gen (
489     & xx_vwind_file, xx_vwindstartdate, xx_vwindperiod,
490     & maskc, tmpVN, xx_vwind0, xx_vwind1, xx_vwind_dummy,
491     & xx_vwind_remo_intercept, xx_vwind_remo_slope,
492     & mytime, myiter, mythid )
493    
494     call rotate_uv2en_rl(tmpUX,tmpVY,tmpUE,tmpVN,
495     & .FALSE.,.FALSE.,.TRUE.,1,mythid)
496    
497     do bj = mybylo(mythid),mybyhi(mythid)
498     do bi = mybxlo(mythid),mybxhi(mythid)
499     do j = 1,sny
500     do i = 1,snx
501     uwind(i,j,bi,bj)=uwind(i,j,bi,bj)+tmpUX(i,j,bi,bj)
502     vwind(i,j,bi,bj)=vwind(i,j,bi,bj)+tmpVY(i,j,bi,bj)
503     enddo
504     enddo
505     enddo
506     enddo
507    
508     #endif
509     #endif /* ALLOW_ROTATE_UV_CONTROLS */
510    
511     #ifdef ALLOW_CARBON
512     #ifdef USE_EXFCO2
513     c Atmospheric carbon dioxide concentration
514     call exf_set_gen (
515     & apco2file, apco2startdate, apco2period,
516     & exf_inscal_apco2,
517     & apco2_exfremo_intercept, apco2_exfremo_slope,
518     & apco2, apco20, apco21, apco2mask,
519     # ifdef USE_EXF_INTERPOLATION
520     & apco2_lon0, apco2_lon_inc, apco2_lat0, apco2_lat_inc,
521     & apco2_nlon, apco2_nlat, xC, yC, interp_method,
522     # endif
523     & mytime, myiter, mythid )
524     #endif
525     #endif
526    
527    
528     cdm transferred from exf_init_runoff.F
529     cdm functionality needs to be checked before turning on
530     cdm #ifdef ALLOW_RUNOFF_CONTROL
531     cdm call ctrl_get_gen (
532     cdm & xx_runoff_file, xx_runoffstartdate, xx_runoffperiod,
533     cdm & maskc, runoff, xx_runoff0, xx_runoff1, xx_runoff_dummy,
534     cdm & xx_runoff_remo_intercept, xx_runoff_remo_slope,
535     cdm & 0., 0., mythid )
536     cdm #endif
537    
538     end

  ViewVC Help
Powered by ViewVC 1.1.22