/[MITgcm]/MITgcm_contrib/ifenty/LatLon/code/exf_getffields.F
ViewVC logotype

Annotation of /MITgcm_contrib/ifenty/LatLon/code/exf_getffields.F

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


Revision 1.1 - (hide annotations) (download)
Wed Jul 5 16:16:43 2006 UTC (19 years ago) by ifenty
Branch: MAIN
CVS Tags: HEAD
Initial checkin of lat-lon configuration of the Lab Sea

1 ifenty 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     #ifdef USE_EXF_INTERPOLATION
58     call exf_set_uv(
59     & ustressfile, ustressstartdate, ustressperiod,
60     & ustressstartdate1, ustressstartdate2,
61     & exf_inscal_ustress, ustress, ustress0, ustress1, ustressmask,
62     & ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
63     & ustress_nlon, ustress_nlat,
64     & ustress_exfremo_intercept, ustress_exfremo_slope,
65     & vstressfile, vstressstartdate, vstressperiod,
66     & vstressstartdate1, vstressstartdate2,
67     & exf_inscal_vstress, vstress, vstress0, vstress1, vstressmask,
68     & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
69     & vstress_nlon, vstress_nlat,
70     & vstress_exfremo_intercept, vstress_exfremo_slope,
71     & mytime, myiter, mythid )
72     #else /* ifndef USE_EXF_INTERPOLATION */
73     call exf_set_gen(
74     & ustressfile, ustressstartdate, ustressperiod,
75     & ustressstartdate1, ustressstartdate2,
76     & exf_inscal_ustress,
77     & ustress_exfremo_intercept, ustress_exfremo_slope,
78     & ustress, ustress0, ustress1, ustressmask,
79     & mytime, myiter, mythid )
80     call exf_set_gen(
81     & vstressfile, vstressstartdate, vstressperiod,
82     & ustressstartdate1, ustressstartdate2,
83     & exf_inscal_vstress,
84     & vstress_exfremo_intercept, vstress_exfremo_slope,
85     & vstress, vstress0, vstress1, vstressmask,
86     & mytime, myiter, mythid )
87     #endif /* USE_EXF_INTERPOLATION */
88    
89     #ifdef ALLOW_ATM_WIND
90    
91     c Zonal and meridional wind.
92     #ifdef USE_EXF_INTERPOLATION
93     call exf_set_uv(
94     & uwindfile, uwindstartdate, uwindperiod,
95     & uwindstartdate1, uwindstartdate2,
96     & exf_inscal_uwind, uwind, uwind0, uwind1, uwindmask,
97     & uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
98     & uwind_nlon, uwind_nlat,
99     & uwind_exfremo_intercept, uwind_exfremo_slope,
100     & vwindfile, vwindstartdate, vwindperiod,
101     & vwindstartdate1, vwindstartdate2,
102     & exf_inscal_vwind, vwind, vwind0, vwind1, vwindmask,
103     & vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
104     & vwind_nlon, vwind_nlat,
105     & vwind_exfremo_intercept, vwind_exfremo_slope,
106     & mytime, myiter, mythid )
107     #else /* ifndef USE_EXF_INTERPOLATION */
108     call exf_set_gen(
109     & uwindfile, uwindstartdate, uwindperiod,
110     & uwindstartdate1, uwindstartdate2,
111     & exf_inscal_uwind,
112     & uwind_exfremo_intercept, uwind_exfremo_slope,
113     & uwind, uwind0, uwind1, uwindmask,
114     & mytime, myiter, mythid )
115     call exf_set_gen(
116     & vwindfile, vwindstartdate, vwindperiod,
117     & vwindstartdate1, vwindstartdate2,
118     & exf_inscal_vwind,
119     & vwind_exfremo_intercept, vwind_exfremo_slope,
120     & vwind, vwind0, vwind1, vwindmask,
121     & mytime, myiter, mythid )
122     #endif /* USE_EXF_INTERPOLATION */
123    
124     #endif /* ALLOW_ATM_WIND */
125    
126     c Atmospheric heat flux.
127     call exf_set_gen (
128     & hfluxfile, hfluxstartdate, hfluxperiod,
129     & hfluxstartdate1, hfluxstartdate2,
130     & exf_inscal_hflux,
131     & hflux_exfremo_intercept, hflux_exfremo_slope,
132     & hflux, hflux0, hflux1, hfluxmask,
133     #ifdef USE_EXF_INTERPOLATION
134     & hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
135     & hflux_nlon, hflux_nlat, xC, yC, interp_method,
136     #endif
137     & mytime, myiter, mythid )
138    
139     c Salt flux.
140     call exf_set_gen (
141     & sfluxfile, sfluxstartdate, sfluxperiod,
142     & sfluxstartdate1, sfluxstartdate2,
143     & exf_inscal_sflux,
144     & sflux_exfremo_intercept, sflux_exfremo_slope,
145     & sflux, sflux0, sflux1, sfluxmask,
146     #ifdef USE_EXF_INTERPOLATION
147     & sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
148     & sflux_nlon, sflux_nlat, xC, yC, interp_method,
149     #endif
150     & mytime, myiter, mythid )
151    
152     #ifdef ALLOW_ATM_TEMP
153    
154     c Atmospheric temperature.
155     call exf_set_gen(
156     & atempfile, atempstartdate, atempperiod,
157     & atempstartdate1, atempstartdate2,
158     & exf_inscal_atemp,
159     & atemp_exfremo_intercept, atemp_exfremo_slope,
160     & atemp, atemp0, atemp1, atempmask,
161     #ifdef USE_EXF_INTERPOLATION
162     & atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
163     & atemp_nlon, atemp_nlat, xC, yC, interp_method,
164     #endif
165     & mytime, myiter, mythid )
166     do bj = mybylo(mythid),mybyhi(mythid)
167     do bi = mybxlo(mythid),mybxhi(mythid)
168     do j = 1,sny
169     do i = 1,snx
170     atemp(i,j,bi,bj) = atemp(i,j,bi,bj) + exf_offset_atemp
171     enddo
172     enddo
173     enddo
174     enddo
175    
176     c Atmospheric humidity.
177     call exf_set_gen(
178     & aqhfile, aqhstartdate, aqhperiod,
179     & aqhstartdate1, aqhstartdate2,
180     & exf_inscal_aqh,
181     & aqh_exfremo_intercept, aqh_exfremo_slope,
182     & aqh, aqh0, aqh1, aqhmask,
183     #ifdef USE_EXF_INTERPOLATION
184     & aqh_lon0, aqh_lon_inc, aqh_lat0, aqh_lat_inc,
185     & aqh_nlon, aqh_nlat, xC, yC, interp_method,
186     #endif
187     & mytime, myiter, mythid )
188    
189     c Net long wave radiative flux.
190     call exf_set_gen(
191     & lwfluxfile, lwfluxstartdate, lwfluxperiod,
192     & lwfluxstartdate1, lwfluxstartdate2,
193     & exf_inscal_lwflux,
194     & lwflux_exfremo_intercept, lwflux_exfremo_slope,
195     & lwflux, lwflux0, lwflux1, lwfluxmask,
196     #ifdef USE_EXF_INTERPOLATION
197     & lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
198     & lwflux_nlon, lwflux_nlat, xC, yC, interp_method,
199     #endif
200     & mytime, myiter, mythid )
201    
202     c Precipitation.
203     call exf_set_gen(
204     & precipfile, precipstartdate, precipperiod,
205     & precipstartdate1, precipstartdate2,
206     & exf_inscal_precip,
207     & precip_exfremo_intercept, precip_exfremo_slope,
208     & precip, precip0, precip1, precipmask,
209     #ifdef USE_EXF_INTERPOLATION
210     & precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
211     & precip_nlon, precip_nlat, xC, yC, interp_method,
212     #endif
213     & mytime, myiter, mythid )
214    
215    
216     c IGF : Precipitation should never be zero although interpolation may allow it to be.
217     do bj = mybylo(mythid),mybyhi(mythid)
218     do bi = mybxlo(mythid),mybxhi(mythid)
219     do j = 1,sny
220     do i = 1,snx
221     precip(i,j,bi,bj) = max(precip(i,j,bi,bj),0)
222     enddo
223     enddo
224     enddo
225     enddo
226    
227    
228    
229     #endif /* ALLOW_ATM_TEMP */
230    
231     #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
232     c Net short wave radiative flux.
233     call exf_set_gen (
234     & swfluxfile, swfluxstartdate, swfluxperiod,
235     & swfluxstartdate1, swfluxstartdate2,
236     & exf_inscal_swflux,
237     & swflux_exfremo_intercept, swflux_exfremo_slope,
238     & swflux, swflux0, swflux1, swfluxmask,
239     #ifdef USE_EXF_INTERPOLATION
240     & swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
241     & swflux_nlon, swflux_nlat, xC, yC, interp_method,
242     #endif
243     & mytime, myiter, mythid )
244     #endif
245    
246     #ifdef EXF_READ_EVAP
247     c Evaporation
248     call exf_set_gen (
249     & evapfile, evapstartdate, evapperiod,
250     & evapstartdate1, evapstartdate2,
251     & exf_inscal_evap,
252     & evap_exfremo_intercept, evap_exfremo_slope,
253     & evap, evap0, evap1, evapmask,
254     #ifdef USE_EXF_INTERPOLATION
255     & evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
256     & evap_nlon, evap_nlat, xC, yC, interp_method,
257     #endif
258     & mytime, myiter, mythid )
259     #endif
260    
261     #ifdef ALLOW_DOWNWARD_RADIATION
262    
263     c Downward shortwave radiation.
264     call exf_set_gen (
265     & swdownfile, swdownstartdate, swdownperiod,
266     & swdownstartdate1, swdownstartdate2,
267     & exf_inscal_swdown,
268     & swdown_exfremo_intercept, swdown_exfremo_slope,
269     & swdown, swdown0, swdown1, swdownmask,
270     #ifdef USE_EXF_INTERPOLATION
271     & swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
272     & swdown_nlon, swdown_nlat, xC, yC, interp_method,
273     #endif
274     & mytime, myiter, mythid )
275    
276     c Downward longwave radiation.
277     call exf_set_gen (
278     & lwdownfile, lwdownstartdate, lwdownperiod,
279     & lwdownstartdate1, lwdownstartdate2,
280     & exf_inscal_lwdown,
281     & lwdown_exfremo_intercept, lwdown_exfremo_slope,
282     & lwdown, lwdown0, lwdown1, lwdownmask,
283     #ifdef USE_EXF_INTERPOLATION
284     & lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
285     & lwdown_nlon, lwdown_nlat, xC, yC, interp_method,
286     #endif
287     & mytime, myiter, mythid )
288    
289     #endif
290    
291     #ifdef ATMOSPHERIC_LOADING
292     c Atmos. pressure forcing
293     call exf_set_gen (
294     & apressurefile, apressurestartdate, apressureperiod,
295     & apressurestartdate1, apressurestartdate2,
296     & exf_inscal_apressure,
297     & apressure_exfremo_intercept, apressure_exfremo_slope,
298     & apressure, apressure0, apressure1, apressuremask,
299     #ifdef USE_EXF_INTERPOLATION
300     & apressure_lon0, apressure_lon_inc, apressure_lat0,
301     & apressure_lat_inc, apressure_nlon, apressure_nlat, xC, yC,
302     & interp_method,
303     #endif
304     & mytime, myiter, mythid )
305     #endif
306    
307     c-- Control variables for atmos. state
308    
309     #ifdef ALLOW_ATEMP_CONTROL
310     call ctrl_get_gen (
311     & xx_atemp_file, xx_atempstartdate, xx_atempperiod,
312     & maskc, atemp, xx_atemp0, xx_atemp1, xx_atemp_dummy,
313     & xx_atemp_remo_intercept, xx_atemp_remo_slope,
314     & mytime, myiter, mythid )
315     #endif
316    
317     #ifdef ALLOW_AQH_CONTROL
318     call ctrl_get_gen (
319     & xx_aqh_file, xx_aqhstartdate, xx_aqhperiod,
320     & maskc, aqh, xx_aqh0, xx_aqh1, xx_aqh_dummy,
321     & xx_aqh_remo_intercept, xx_aqh_remo_slope,
322     & mytime, myiter, mythid )
323     #endif
324    
325     #ifdef ALLOW_PRECIP_CONTROL
326     call ctrl_get_gen (
327     & xx_precip_file, xx_precipstartdate, xx_precipperiod,
328     & maskc, precip, xx_precip0, xx_precip1, xx_precip_dummy,
329     & xx_precip_remo_intercept, xx_precip_remo_slope,
330     & mytime, myiter, mythid )
331     #endif
332    
333     #ifdef ALLOW_SWFLUX_CONTROL
334     call ctrl_get_gen (
335     & xx_swflux_file, xx_swfluxstartdate, xx_swfluxperiod,
336     & maskc, swflux, xx_swflux0, xx_swflux1, xx_swflux_dummy,
337     & xx_swflux_remo_intercept, xx_swflux_remo_slope,
338     & mytime, myiter, mythid )
339     #endif
340    
341     #ifdef ALLOW_SWDOWN_CONTROL
342     call ctrl_get_gen (
343     & xx_swdown_file, xx_swdownstartdate, xx_swdownperiod,
344     & maskc, swdown, xx_swdown0, xx_swdown1, xx_swdown_dummy,
345     & xx_swdown_remo_intercept, xx_swdown_remo_slope,
346     & mytime, myiter, mythid )
347     #endif
348    
349     #ifdef ALLOW_UWIND_CONTROL
350     call ctrl_get_gen (
351     & xx_uwind_file, xx_uwindstartdate, xx_uwindperiod,
352     & maskc, uwind, xx_uwind0, xx_uwind1, xx_uwind_dummy,
353     & xx_uwind_remo_intercept, xx_uwind_remo_slope,
354     & mytime, myiter, mythid )
355     #endif /* ALLOW_UWIND_CONTROL */
356    
357     #ifdef ALLOW_VWIND_CONTROL
358     call ctrl_get_gen (
359     & xx_vwind_file, xx_vwindstartdate, xx_vwindperiod,
360     & maskc, vwind, xx_vwind0, xx_vwind1, xx_vwind_dummy,
361     & xx_vwind_remo_intercept, xx_vwind_remo_slope,
362     & mytime, myiter, mythid )
363     #endif /* ALLOW_VWIND_CONTROL */
364    
365     #ifdef ALLOW_LWFLUX_CONTROL
366     call ctrl_get_gen (
367     NOT YET IMPLEMENTED
368     & mytime, myiter, mythid )
369     #endif
370    
371    
372     end

  ViewVC Help
Powered by ViewVC 1.1.22