/[MITgcm]/MITgcm_contrib/SOSE/code_ad/exf_getffields.F
ViewVC logotype

Annotation of /MITgcm_contrib/SOSE/code_ad/exf_getffields.F

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


Revision 1.1 - (hide annotations) (download)
Fri Apr 23 19:55:12 2010 UTC (15 years, 3 months ago) by mmazloff
Branch: MAIN
CVS Tags: HEAD
original files

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

  ViewVC Help
Powered by ViewVC 1.1.22