/[MITgcm]/MITgcm_contrib/sannino/OASIS_3.0_Coupler/code/exf_getffields.F
ViewVC logotype

Annotation of /MITgcm_contrib/sannino/OASIS_3.0_Coupler/code/exf_getffields.F

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


Revision 1.1 - (hide annotations) (download)
Thu Jul 20 21:08:15 2006 UTC (19 years ago) by sannino
Branch: MAIN
CVS Tags: HEAD
o Adding OASIS package
o Adding grid refinement package

1 sannino 1.1 C
2     C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_getffields.F,v 1.31 2006/03/02 15:30:10 heimbach Exp $
3     C $Name: $
4    
5     #include "EXF_OPTIONS.h"
6    
7     subroutine exf_getffields( mytime, myiter, mythid )
8    
9     c ==================================================================
10     c SUBROUTINE exf_getffields
11     c ==================================================================
12     c
13     c o Read-in atmospheric state and/or surface fluxes from files.
14     c
15     c heimbach@mit.edu, 23-May-2003 totally re-structured
16     c 5-Aug-2003: added USE_EXF_INTERPOLATION for arbitrary input grid
17     c
18     c ==================================================================
19     c SUBROUTINE exf_getffields
20     c ==================================================================
21    
22     implicit none
23    
24     c == global variables ==
25    
26     #include "EEPARAMS.h"
27     #include "SIZE.h"
28     #include "PARAMS.h"
29     #include "DYNVARS.h"
30     #include "GRID.h"
31    
32     #include "exf_param.h"
33     #include "exf_fields.h"
34     #include "exf_constants.h"
35    
36     #ifdef ALLOW_AUTODIFF
37     # include "ctrl.h"
38     # include "ctrl_dummy.h"
39     #endif
40    
41     c == routine arguments ==
42    
43     integer mythid
44     integer myiter
45     _RL mytime
46    
47     c == local variables ==
48    
49     integer i, j, bi, bj, interp_method
50     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     cgmOASIS(
58     #ifdef ALLOW_OASIS
59     #ifdef USE_EXF_INTERPOLATION
60     call exf_set_uv(
61     & ustressfile, ustressstartdate, ustressperiod,
62     & ustressstartdate1, ustressstartdate2,
63     & exf_inscal_ustress, ustress, ustress0, ustress1, ustressmask,
64     & ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
65     & ustress_nlon, ustress_nlat,
66     & ustress_exfremo_intercept, ustress_exfremo_slope,
67     & vstressfile, vstressstartdate, vstressperiod,
68     & vstressstartdate1, vstressstartdate2,
69     & exf_inscal_vstress, vstress, vstress0, vstress1, vstressmask,
70     & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
71     & vstress_nlon, vstress_nlat,
72     & vstress_exfremo_intercept, vstress_exfremo_slope,
73     & mytime, myiter, mythid )
74     #else /* ifndef USE_EXF_INTERPOLATION */
75     call oasis_set_gen(
76     & ustressfile, ustressstartdate, ustressperiod,
77     & ustressstartdate1, ustressstartdate2,
78     & exf_inscal_ustress,
79     & ustress, ustress0, ustress1, ustressmask,
80     & mytime, myiter, mythid, 2 ) !idFieldOASIS (4 nel caso dell'altra variabile)
81     call oasis_set_gen(
82     & vstressfile, vstressstartdate, vstressperiod,
83     & ustressstartdate1, ustressstartdate2,
84     & exf_inscal_vstress,
85     & vstress, vstress0, vstress1, vstressmask,
86     & mytime, myiter, mythid, 5 ) !idFieldOASIS (3 nel caso dell'altra variabile)
87     cc ** N.B. Duplico la chiamata **
88     call oasis_set_gen(
89     & ustressfile, ustressstartdate, ustressperiod,
90     & ustressstartdate1, ustressstartdate2,
91     & exf_inscal_ustress,
92     & ustress, ustress0, ustress1, ustressmask,
93     & mytime, myiter, mythid, 4 ) !idFieldOASIS (4 nel caso dell'altra variabile)
94     call oasis_set_gen(
95     & vstressfile, vstressstartdate, vstressperiod,
96     & ustressstartdate1, ustressstartdate2,
97     & exf_inscal_vstress,
98     & vstress, vstress0, vstress1, vstressmask,
99     & mytime, myiter, mythid, 3 ) !idFieldOASIS (3 nel caso dell'altra variabile)
100     c***** N.B. ****
101     #endif /* USE_EXF_INTERPOLATION */
102     #else /* ALLOW_OASIS */
103     #ifdef USE_EXF_INTERPOLATION
104     call exf_set_uv(
105     & ustressfile, ustressstartdate, ustressperiod,
106     & ustressstartdate1, ustressstartdate2,
107     & exf_inscal_ustress, ustress, ustress0, ustress1, ustressmask,
108     & ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
109     & ustress_nlon, ustress_nlat,
110     & ustress_exfremo_intercept, ustress_exfremo_slope,
111     & vstressfile, vstressstartdate, vstressperiod,
112     & vstressstartdate1, vstressstartdate2,
113     & exf_inscal_vstress, vstress, vstress0, vstress1, vstressmask,
114     & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
115     & vstress_nlon, vstress_nlat,
116     & vstress_exfremo_intercept, vstress_exfremo_slope,
117     & mytime, myiter, mythid )
118     #else /* ifndef USE_EXF_INTERPOLATION */
119     call exf_set_gen(
120     & ustressfile, ustressstartdate, ustressperiod,
121     & ustressstartdate1, ustressstartdate2,
122     & exf_inscal_ustress,
123     & ustress_exfremo_intercept, ustress_exfremo_slope,
124     & ustress, ustress0, ustress1, ustressmask,
125     & mytime, myiter, mythid )
126     call exf_set_gen(
127     & vstressfile, vstressstartdate, vstressperiod,
128     & ustressstartdate1, ustressstartdate2,
129     & exf_inscal_vstress,
130     & vstress_exfremo_intercept, vstress_exfremo_slope,
131     & vstress, vstress0, vstress1, vstressmask,
132     & mytime, myiter, mythid )
133     #endif /* USE_EXF_INTERPOLATION */
134     #endif /* ALLOW_OASIS */
135     cgmOASIS)
136    
137    
138    
139    
140     cgmEXF(
141     c Relaxation Time for SST (gammaT)
142     call exf_set_gen (
143     & gammaTfile, gammaTstartdate,gammaTperiod,
144     & gammaTstartdate1, gammaTstartdate2,
145     & exf_inscal_gammaT,
146     & gammaT_exfremo_intercept, gammaT_exfremo_slope,
147     & gammaT, gammaT0, gammaT1, gammaTmask,
148     #ifdef USE_EXF_INTERPOLATION
149     & gammaT_lon0, gammaT_lon_inc, gammaT_lat0, gammaT_lat_inc,
150     & gammaT_nlon, gammaT_nlat, xC, yC,interp_method,
151     #endif
152     & mytime, myiter, mythid )
153    
154     cgmEXF)
155    
156    
157    
158     #ifdef ALLOW_ATM_WIND
159    
160     c Zonal and meridional wind.
161     #ifdef USE_EXF_INTERPOLATION
162     call exf_set_uv(
163     & uwindfile, uwindstartdate, uwindperiod,
164     & uwindstartdate1, uwindstartdate2,
165     & exf_inscal_uwind, uwind, uwind0, uwind1, uwindmask,
166     & uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
167     & uwind_nlon, uwind_nlat,
168     & uwind_exfremo_intercept, uwind_exfremo_slope,
169     & vwindfile, vwindstartdate, vwindperiod,
170     & vwindstartdate1, vwindstartdate2,
171     & exf_inscal_vwind, vwind, vwind0, vwind1, vwindmask,
172     & vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
173     & vwind_nlon, vwind_nlat,
174     & vwind_exfremo_intercept, vwind_exfremo_slope,
175     & mytime, myiter, mythid )
176     #else /* ifndef USE_EXF_INTERPOLATION */
177     call exf_set_gen(
178     & uwindfile, uwindstartdate, uwindperiod,
179     & uwindstartdate1, uwindstartdate2,
180     & exf_inscal_uwind,
181     & uwind_exfremo_intercept, uwind_exfremo_slope,
182     & uwind, uwind0, uwind1, uwindmask,
183     & mytime, myiter, mythid )
184     call exf_set_gen(
185     & vwindfile, vwindstartdate, vwindperiod,
186     & vwindstartdate1, vwindstartdate2,
187     & exf_inscal_vwind,
188     & vwind_exfremo_intercept, vwind_exfremo_slope,
189     & vwind, vwind0, vwind1, vwindmask,
190     & mytime, myiter, mythid )
191     #endif /* USE_EXF_INTERPOLATION */
192    
193     #endif /* ALLOW_ATM_WIND */
194    
195     c Atmospheric heat flux.
196     cgmOASIS(
197     #ifdef ALLOW_OASIS
198     call oasis_set_gen (
199     & hfluxfile, hfluxstartdate, hfluxperiod,
200     & hfluxstartdate1, hfluxstartdate2,
201     & exf_inscal_hflux,
202     & hflux, hflux0, hflux1, hfluxmask,
203     & mytime, myiter, mythid , 1 ) !idFieldOASIS
204     #else /* ALLOW_OASIS */
205     call exf_set_gen (
206     & hfluxfile, hfluxstartdate, hfluxperiod,
207     & hfluxstartdate1, hfluxstartdate2,
208     & exf_inscal_hflux,
209     & hflux_exfremo_intercept, hflux_exfremo_slope,
210     & hflux, hflux0, hflux1, hfluxmask,
211     #ifdef USE_EXF_INTERPOLATION
212     & hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
213     & hflux_nlon, hflux_nlat, xC, yC, interp_method,
214     #endif
215     & mytime, myiter, mythid )
216     #endif /* ALLOW_OASIS */
217     cgmOASIS)
218    
219    
220     c Salt flux.
221     call exf_set_gen (
222     & sfluxfile, sfluxstartdate, sfluxperiod,
223     & sfluxstartdate1, sfluxstartdate2,
224     & exf_inscal_sflux,
225     & sflux_exfremo_intercept, sflux_exfremo_slope,
226     & sflux, sflux0, sflux1, sfluxmask,
227     #ifdef USE_EXF_INTERPOLATION
228     & sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
229     & sflux_nlon, sflux_nlat, xC, yC, interp_method,
230     #endif
231     & mytime, myiter, mythid )
232    
233     #ifdef ALLOW_ATM_TEMP
234    
235     c Atmospheric temperature.
236     call exf_set_gen(
237     & atempfile, atempstartdate, atempperiod,
238     & atempstartdate1, atempstartdate2,
239     & exf_inscal_atemp,
240     & atemp_exfremo_intercept, atemp_exfremo_slope,
241     & atemp, atemp0, atemp1, atempmask,
242     #ifdef USE_EXF_INTERPOLATION
243     & atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
244     & atemp_nlon, atemp_nlat, xC, yC, interp_method,
245     #endif
246     & mytime, myiter, mythid )
247     do bj = mybylo(mythid),mybyhi(mythid)
248     do bi = mybxlo(mythid),mybxhi(mythid)
249     do j = 1,sny
250     do i = 1,snx
251     atemp(i,j,bi,bj) = atemp(i,j,bi,bj) + exf_offset_atemp
252     enddo
253     enddo
254     enddo
255     enddo
256    
257     c Atmospheric humidity.
258     call exf_set_gen(
259     & aqhfile, aqhstartdate, aqhperiod,
260     & aqhstartdate1, aqhstartdate2,
261     & exf_inscal_aqh,
262     & aqh_exfremo_intercept, aqh_exfremo_slope,
263     & aqh, aqh0, aqh1, aqhmask,
264     #ifdef USE_EXF_INTERPOLATION
265     & aqh_lon0, aqh_lon_inc, aqh_lat0, aqh_lat_inc,
266     & aqh_nlon, aqh_nlat, xC, yC, interp_method,
267     #endif
268     & mytime, myiter, mythid )
269    
270     c Net long wave radiative flux.
271     call exf_set_gen(
272     & lwfluxfile, lwfluxstartdate, lwfluxperiod,
273     & lwfluxstartdate1, lwfluxstartdate2,
274     & exf_inscal_lwflux,
275     & lwflux_exfremo_intercept, lwflux_exfremo_slope,
276     & lwflux, lwflux0, lwflux1, lwfluxmask,
277     #ifdef USE_EXF_INTERPOLATION
278     & lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
279     & lwflux_nlon, lwflux_nlat, xC, yC, interp_method,
280     #endif
281     & mytime, myiter, mythid )
282    
283     c Precipitation.
284     call exf_set_gen(
285     & precipfile, precipstartdate, precipperiod,
286     & precipstartdate1, precipstartdate2,
287     & exf_inscal_precip,
288     & precip_exfremo_intercept, precip_exfremo_slope,
289     & precip, precip0, precip1, precipmask,
290     #ifdef USE_EXF_INTERPOLATION
291     & precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
292     & precip_nlon, precip_nlat, xC, yC, interp_method,
293     #endif
294     & mytime, myiter, mythid )
295    
296    
297     cgmEXF(
298     c Total Cloud Cover(cloudC)
299     call exf_set_gen (
300     & cloudCfile, cloudCstartdate,cloudCperiod,
301     & cloudCstartdate1, cloudCstartdate2,
302     & exf_inscal_cloudC,
303     & cloudC_exfremo_intercept, cloudC_exfremo_slope,
304     & cloudC, cloudC0, cloudC1, cloudCmask,
305     #ifdef USE_EXF_INTERPOLATION
306     & cloudC_lon0, cloudC_lon_inc, cloudC_lat0, cloudC_lat_inc,
307     & cloudC_nlon, cloudC_nlat, xC, yC, interp_method,
308     #endif
309     & mytime, myiter, mythid )
310    
311     c Relative Humidity
312     call exf_set_gen (
313     & dewpTfile, dewpTstartdate,dewpTperiod,
314     & dewpTstartdate1, dewpTstartdate2,
315     & exf_inscal_dewpT,
316     & dewpT_exfremo_intercept, dewpT_exfremo_slope,
317     & dewpT, dewpT0, dewpT1, dewpTmask,
318     #ifdef USE_EXF_INTERPOLATION
319     & dewpT_lon0, dewpT_lon_inc, dewpT_lat0, dewpT_lat_inc,
320     & dewpT_nlon, dewpT_nlat, xC, yC,interp_method,
321     #endif
322     & mytime, myiter, mythid )
323    
324     cgmEXF)
325    
326    
327    
328    
329    
330    
331     #endif /* ALLOW_ATM_TEMP */
332    
333     #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
334     c Net short wave radiative flux.
335     call exf_set_gen (
336     & swfluxfile, swfluxstartdate, swfluxperiod,
337     & swfluxstartdate1, swfluxstartdate2,
338     & exf_inscal_swflux,
339     & swflux_exfremo_intercept, swflux_exfremo_slope,
340     & swflux, swflux0, swflux1, swfluxmask,
341     #ifdef USE_EXF_INTERPOLATION
342     & swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
343     & swflux_nlon, swflux_nlat, xC, yC, interp_method,
344     #endif
345     & mytime, myiter, mythid )
346     #endif
347    
348     #ifdef EXF_READ_EVAP
349     c Evaporation
350     call exf_set_gen (
351     & evapfile, evapstartdate, evapperiod,
352     & evapstartdate1, evapstartdate2,
353     & exf_inscal_evap,
354     & evap_exfremo_intercept, evap_exfremo_slope,
355     & evap, evap0, evap1, evapmask,
356     #ifdef USE_EXF_INTERPOLATION
357     & evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
358     & evap_nlon, evap_nlat, xC, yC, interp_method,
359     #endif
360     & mytime, myiter, mythid )
361     #endif
362    
363     #ifdef ALLOW_DOWNWARD_RADIATION
364    
365     c Downward shortwave radiation.
366     call exf_set_gen (
367     & swdownfile, swdownstartdate, swdownperiod,
368     & swdownstartdate1, swdownstartdate2,
369     & exf_inscal_swdown,
370     & swdown_exfremo_intercept, swdown_exfremo_slope,
371     & swdown, swdown0, swdown1, swdownmask,
372     #ifdef USE_EXF_INTERPOLATION
373     & swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
374     & swdown_nlon, swdown_nlat, xC, yC, interp_method,
375     #endif
376     & mytime, myiter, mythid )
377    
378     c Downward longwave radiation.
379     call exf_set_gen (
380     & lwdownfile, lwdownstartdate, lwdownperiod,
381     & lwdownstartdate1, lwdownstartdate2,
382     & exf_inscal_lwdown,
383     & lwdown_exfremo_intercept, lwdown_exfremo_slope,
384     & lwdown, lwdown0, lwdown1, lwdownmask,
385     #ifdef USE_EXF_INTERPOLATION
386     & lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
387     & lwdown_nlon, lwdown_nlat, xC, yC, interp_method,
388     #endif
389     & mytime, myiter, mythid )
390    
391     #endif
392    
393     #ifdef ATMOSPHERIC_LOADING
394     c Atmos. pressure forcing
395     call exf_set_gen (
396     & apressurefile, apressurestartdate, apressureperiod,
397     & apressurestartdate1, apressurestartdate2,
398     & exf_inscal_apressure,
399     & apressure_exfremo_intercept, apressure_exfremo_slope,
400     & apressure, apressure0, apressure1, apressuremask,
401     #ifdef USE_EXF_INTERPOLATION
402     & apressure_lon0, apressure_lon_inc, apressure_lat0,
403     & apressure_lat_inc, apressure_nlon, apressure_nlat, xC, yC,
404     & interp_method,
405     #endif
406     & mytime, myiter, mythid )
407     #endif
408    
409     c-- Control variables for atmos. state
410    
411     #ifdef ALLOW_ATEMP_CONTROL
412     call ctrl_get_gen (
413     & xx_atemp_file, xx_atempstartdate, xx_atempperiod,
414     & maskc, atemp, xx_atemp0, xx_atemp1, xx_atemp_dummy,
415     & xx_atemp_remo_intercept, xx_atemp_remo_slope,
416     & mytime, myiter, mythid )
417     #endif
418    
419     #ifdef ALLOW_AQH_CONTROL
420     call ctrl_get_gen (
421     & xx_aqh_file, xx_aqhstartdate, xx_aqhperiod,
422     & maskc, aqh, xx_aqh0, xx_aqh1, xx_aqh_dummy,
423     & xx_aqh_remo_intercept, xx_aqh_remo_slope,
424     & mytime, myiter, mythid )
425     #endif
426    
427     #ifdef ALLOW_PRECIP_CONTROL
428     call ctrl_get_gen (
429     & xx_precip_file, xx_precipstartdate, xx_precipperiod,
430     & maskc, precip, xx_precip0, xx_precip1, xx_precip_dummy,
431     & xx_precip_remo_intercept, xx_precip_remo_slope,
432     & mytime, myiter, mythid )
433     #endif
434    
435     #ifdef ALLOW_SWFLUX_CONTROL
436     call ctrl_get_gen (
437     & xx_swflux_file, xx_swfluxstartdate, xx_swfluxperiod,
438     & maskc, swflux, xx_swflux0, xx_swflux1, xx_swflux_dummy,
439     & xx_swflux_remo_intercept, xx_swflux_remo_slope,
440     & mytime, myiter, mythid )
441     #endif
442    
443     #ifdef ALLOW_SWDOWN_CONTROL
444     call ctrl_get_gen (
445     & xx_swdown_file, xx_swdownstartdate, xx_swdownperiod,
446     & maskc, swdown, xx_swdown0, xx_swdown1, xx_swdown_dummy,
447     & xx_swdown_remo_intercept, xx_swdown_remo_slope,
448     & mytime, myiter, mythid )
449     #endif
450    
451     #ifdef ALLOW_UWIND_CONTROL
452     call ctrl_get_gen (
453     & xx_uwind_file, xx_uwindstartdate, xx_uwindperiod,
454     & maskc, uwind, xx_uwind0, xx_uwind1, xx_uwind_dummy,
455     & xx_uwind_remo_intercept, xx_uwind_remo_slope,
456     & mytime, myiter, mythid )
457     #endif /* ALLOW_UWIND_CONTROL */
458    
459     #ifdef ALLOW_VWIND_CONTROL
460     call ctrl_get_gen (
461     & xx_vwind_file, xx_vwindstartdate, xx_vwindperiod,
462     & maskc, vwind, xx_vwind0, xx_vwind1, xx_vwind_dummy,
463     & xx_vwind_remo_intercept, xx_vwind_remo_slope,
464     & mytime, myiter, mythid )
465     #endif /* ALLOW_VWIND_CONTROL */
466    
467     #ifdef ALLOW_LWFLUX_CONTROL
468     call ctrl_get_gen (
469     NOT YET IMPLEMENTED
470     & mytime, myiter, mythid )
471     #endif
472    
473    
474     end

  ViewVC Help
Powered by ViewVC 1.1.22