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

Annotation of /MITgcm_contrib/SOSE/code_ad/exf_init.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_init.F,v 1.21 2009/02/16 09:10:18 mlosch Exp $
2     C $Name: $
3    
4     #include "EXF_OPTIONS.h"
5    
6    
7     subroutine exf_init( mythid )
8    
9     c ==================================================================
10     c SUBROUTINE exf_init
11     c ==================================================================
12     c
13     c o This routine initialises the forcing
14     c
15     c started: Ralf.Giering@FastOpt.de 25-Mai-20000
16     c mods for pkg/seaice: menemenlis@jpl.nasa.gov 20-Dec-2002
17     c
18     c ==================================================================
19     c SUBROUTINE exf_init
20     c ==================================================================
21    
22     implicit none
23    
24     c == global variables ==
25    
26     #include "EEPARAMS.h"
27     #include "SIZE.h"
28     #include "GRID.h"
29     #include "cal.h"
30     #include "EXF_PARAM.h"
31     #include "EXF_FIELDS.h"
32    
33     c == routine arguments ==
34    
35     integer mythid
36    
37     c == local variables ==
38    
39     integer interp_method
40     INTEGER i,j,bi,bj
41    
42     c == end of interface ==
43    
44     C-- Initialise to zero intermediate fields (in common block)
45     DO bj = myByLo(myThid), myByHi(myThid)
46     DO bi = myBxLo(myThid), myBxHi(myThid)
47     DO j=1-Oly,sNy+Oly
48     DO i=1-Olx,sNx+Olx
49     wStress(i,j,bi,bj) = 0.
50     cw(i,j,bi,bj) = 0.
51     sw(i,j,bi,bj) = 0.
52     sh(i,j,bi,bj) = 0.
53     #ifdef ALLOW_ATM_TEMP
54     hs(i,j,bi,bj) = 0.
55     hl(i,j,bi,bj) = 0.
56     #endif
57     ENDDO
58     ENDDO
59     ENDDO
60     ENDDO
61    
62     if ( useCubedSphereExchange
63     & .and. ustressperiod .eq. 0
64     & .and. ustressfile .NE. ' ' ) then
65     stop 'CubedSphereExchange and ustressperiod=0 not supported'
66     endif
67     interp_method=12
68     call exf_init_gen (
69     & ustressfile, ustressperiod, exf_inscal_ustress, ustressmask,
70     & ustressconst, ustress, ustress0, ustress1,
71     #ifdef USE_EXF_INTERPOLATION
72     & ustress_lon0, ustress_lon_inc,
73     & ustress_lat0, ustress_lat_inc,
74     & ustress_nlon, ustress_nlat, xC, yC, interp_method,
75     #endif
76     & mythid )
77    
78     if ( useCubedSphereExchange
79     & .and. vstressperiod .eq. 0
80     & .and. vstressfile .NE. ' ' ) then
81     stop 'CubedSphereExchange and vstressperiod=0 not supported'
82     endif
83     interp_method=22
84     call exf_init_gen (
85     & vstressfile, vstressperiod, exf_inscal_vstress, vstressmask,
86     & vstressconst, vstress, vstress0, vstress1,
87     #ifdef USE_EXF_INTERPOLATION
88     & vstress_lon0, vstress_lon_inc,
89     & vstress_lat0, vstress_lat_inc,
90     & vstress_nlon, vstress_nlat, xC, yC, interp_method,
91     #endif
92     & mythid )
93    
94     #ifdef ALLOW_ATM_WIND
95    
96     if ( useCubedSphereExchange
97     & .and. uwindperiod .eq. 0
98     & .and. uwindfile .NE. ' ' ) then
99     stop 'CubedSphereExchange and uwindperiod=0 not supported'
100     endif
101     interp_method=12
102     call exf_init_gen (
103     & uwindfile, uwindperiod, exf_inscal_uwind, uwindmask,
104     & uwindconst, uwind, uwind0, uwind1,
105     #ifdef USE_EXF_INTERPOLATION
106     & uwind_lon0, uwind_lon_inc,
107     & uwind_lat0, uwind_lat_inc,
108     & uwind_nlon, uwind_nlat, xC, yC, interp_method,
109     #endif
110     & mythid )
111    
112     if ( useCubedSphereExchange
113     & .and. vwindperiod .eq. 0
114     & .and. vwindfile .NE. ' ' ) then
115     stop 'CubedSphereExchange and vwindperiod=0 not supported'
116     endif
117     interp_method=22
118     call exf_init_gen (
119     & vwindfile, vwindperiod, exf_inscal_vwind, vwindmask,
120     & vwindconst, vwind, vwind0, vwind1,
121     #ifdef USE_EXF_INTERPOLATION
122     & vwind_lon0, vwind_lon_inc,
123     & vwind_lat0, vwind_lat_inc,
124     & vwind_nlon, vwind_nlat, xC, yC, interp_method,
125     #endif
126     & mythid )
127    
128     #endif /* ALLOW_ATM_WIND */
129    
130     CMM interp_method=1
131     interp_method=2
132    
133     call exf_init_gen (
134     & wspeedfile, wspeedperiod, exf_inscal_wspeed, wspeedmask,
135     & wspeedconst, wspeed, wspeed0, wspeed1,
136     #ifdef USE_EXF_INTERPOLATION
137     & wspeed_lon0, wspeed_lon_inc,
138     & wspeed_lat0, wspeed_lat_inc,
139     & wspeed_nlon, wspeed_nlat, xC, yC, interp_method,
140     #endif
141     & mythid )
142    
143     call exf_init_gen (
144     & hfluxfile, hfluxperiod, exf_inscal_hflux, hfluxmask,
145     & hfluxconst, hflux, hflux0, hflux1,
146     #ifdef USE_EXF_INTERPOLATION
147     & hflux_lon0, hflux_lon_inc,
148     & hflux_lat0, hflux_lat_inc,
149     & hflux_nlon, hflux_nlat, xC, yC, interp_method,
150     #endif
151     & mythid )
152    
153     call exf_init_gen (
154     & sfluxfile, sfluxperiod, exf_inscal_sflux, sfluxmask,
155     & sfluxconst, sflux, sflux0, sflux1,
156     #ifdef USE_EXF_INTERPOLATION
157     & sflux_lon0, sflux_lon_inc,
158     & sflux_lat0, sflux_lat_inc,
159     & sflux_nlon, sflux_nlat, xC, yC, interp_method,
160     #endif
161     & mythid )
162    
163     #ifdef ALLOW_ATM_TEMP
164    
165     call exf_init_gen (
166     & atempfile, atempperiod, exf_inscal_atemp, atempmask,
167     & atempconst, atemp, atemp0, atemp1,
168     #ifdef USE_EXF_INTERPOLATION
169     & atemp_lon0, atemp_lon_inc,
170     & atemp_lat0, atemp_lat_inc,
171     & atemp_nlon, atemp_nlat, xC, yC, interp_method,
172     #endif
173     & mythid )
174    
175     call exf_init_gen (
176     & aqhfile, aqhperiod, exf_inscal_aqh, aqhmask,
177     & aqhconst, aqh, aqh0, aqh1,
178     #ifdef USE_EXF_INTERPOLATION
179     & aqh_lon0, aqh_lon_inc,
180     & aqh_lat0, aqh_lat_inc,
181     & aqh_nlon, aqh_nlat, xC, yC, interp_method,
182     #endif
183     & mythid )
184    
185     call exf_init_gen (
186     & lwfluxfile, lwfluxperiod, exf_inscal_lwflux, lwfluxmask,
187     & lwfluxconst, lwflux, lwflux0, lwflux1,
188     #ifdef USE_EXF_INTERPOLATION
189     & lwflux_lon0, lwflux_lon_inc,
190     & lwflux_lat0, lwflux_lat_inc,
191     & lwflux_nlon, lwflux_nlat, xC, yC, interp_method,
192     #endif
193     & mythid )
194    
195     call exf_init_gen (
196     & precipfile, precipperiod, exf_inscal_precip, precipmask,
197     & precipconst, precip, precip0, precip1,
198     #ifdef USE_EXF_INTERPOLATION
199     & precip_lon0, precip_lon_inc,
200     & precip_lat0, precip_lat_inc,
201     & precip_nlon, precip_nlat, xC, yC, interp_method,
202     #endif
203     & mythid )
204    
205     call exf_init_gen (
206     & snowprecipfile, snowprecipperiod,
207     & exf_inscal_snowprecip, snowprecipmask,
208     & snowprecipconst, snowprecip, snowprecip0, snowprecip1,
209     #ifdef USE_EXF_INTERPOLATION
210     & snowprecip_lon0, snowprecip_lon_inc,
211     & snowprecip_lat0, snowprecip_lat_inc,
212     & snowprecip_nlon, snowprecip_nlat, xC, yC, interp_method,
213     #endif
214     & mythid )
215    
216     #endif /* ALLOW_ATM_TEMP */
217    
218     #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
219     call exf_init_gen (
220     & swfluxfile, swfluxperiod, exf_inscal_swflux, swfluxmask,
221     & swfluxconst, swflux, swflux0, swflux1,
222     #ifdef USE_EXF_INTERPOLATION
223     & swflux_lon0, swflux_lon_inc,
224     & swflux_lat0, swflux_lat_inc,
225     & swflux_nlon, swflux_nlat, xC, yC, interp_method,
226     #endif
227     & mythid )
228     #endif /* defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING) */
229    
230     #if defined(ALLOW_ATM_TEMP) || defined(EXF_READ_EVAP)
231     call exf_init_gen (
232     & evapfile, evapperiod, exf_inscal_evap, evapmask,
233     & evapconst, evap, evap0, evap1,
234     #ifdef USE_EXF_INTERPOLATION
235     & evap_lon0, evap_lon_inc,
236     & evap_lat0, evap_lat_inc,
237     & evap_nlon, evap_nlat, xC, yC, interp_method,
238     #endif
239     & mythid )
240     #endif /* defined(ALLOW_ATM_TEMP) || defined(EXF_READ_EVAP) */
241    
242     #ifdef ALLOW_DOWNWARD_RADIATION
243    
244     call exf_init_gen (
245     & swdownfile, swdownperiod, exf_inscal_swdown, swdownmask,
246     & swdownconst, swdown, swdown0, swdown1,
247     #ifdef USE_EXF_INTERPOLATION
248     & swdown_lon0, swdown_lon_inc,
249     & swdown_lat0, swdown_lat_inc,
250     & swdown_nlon, swdown_nlat, xC, yC, interp_method,
251     #endif
252     & mythid )
253    
254     call exf_init_gen (
255     & lwdownfile, lwdownperiod, exf_inscal_lwdown, lwdownmask,
256     & lwdownconst, lwdown, lwdown0, lwdown1,
257     #ifdef USE_EXF_INTERPOLATION
258     & lwdown_lon0, lwdown_lon_inc,
259     & lwdown_lat0, lwdown_lat_inc,
260     & lwdown_nlon, lwdown_nlat, xC, yC, interp_method,
261     #endif
262     & mythid )
263    
264     #endif /* ALLOW_DOWNWARD_RADIATION */
265    
266     #ifdef ATMOSPHERIC_LOADING
267     call exf_init_gen (
268     & apressurefile, apressureperiod,
269     & exf_inscal_apressure, apressuremask,
270     & apressureconst, apressure, apressure0, apressure1,
271     #ifdef USE_EXF_INTERPOLATION
272     & apressure_lon0, apressure_lon_inc,
273     & apressure_lat0, apressure_lat_inc,
274     & apressure_nlon, apressure_nlat, xC, yC, interp_method,
275     #endif
276     & mythid )
277     #endif /* ATMOSPHERIC_LOADING */
278    
279     #ifdef ALLOW_ICE_AREAMASK
280     call exf_init_gen (
281     & areamaskfile, areamaskperiod,
282     & exf_inscal_areamask, areamaskmask,
283     & areamaskconst, areamask, areamask0, areamask1,
284     #ifdef USE_EXF_INTERPOLATION
285     & areamask_lon0, areamask_lon_inc,
286     & areamask_lat0, areamask_lat_inc,
287     & areamask_nlon, areamask_nlat, xC, yC, interp_method,
288     #endif
289     & mythid )
290     #endif /* ALLOW_ICE_AREAMASK */
291    
292     #ifdef ALLOW_RUNOFF
293     #ifdef USE_NO_INTERP_RUNOFF
294     call exf_init_runoff (
295     & runofffile, runoffperiod, exf_inscal_runoff, runoffmask,
296     & runoffconst, runoff, runoff0, runoff1,
297     & mythid )
298     #else /* ndef USE_NO_INTERP_RUNOFF */
299     call exf_init_gen (
300     & runofffile, runoffperiod, exf_inscal_runoff, runoffmask,
301     & runoffconst, runoff, runoff0, runoff1,
302     #ifdef USE_EXF_INTERPOLATION
303     & runoff_lon0, runoff_lon_inc,
304     & runoff_lat0, runoff_lat_inc,
305     & runoff_nlon, runoff_nlat, xC, yC, interp_method,
306     #endif
307     & mythid )
308     #endif /* def USE_NO_INTERP_RUNOFF */
309     #endif /* ALLOW_RUNOFF */
310    
311     #ifdef ALLOW_CLIMSST_RELAXATION
312     interp_method=2
313     call exf_init_gen (
314     & climsstfile, climsstperiod, exf_inscal_climsst, climsstmask,
315     & climsstconst, climsst, climsst0, climsst1,
316     #ifdef USE_EXF_INTERPOLATION
317     & climsst_lon0, climsst_lon_inc,
318     & climsst_lat0, climsst_lat_inc,
319     & climsst_nlon, climsst_nlat, xC, yC, interp_method,
320     #endif
321     & mythid )
322     #endif
323    
324     #ifdef ALLOW_CLIMSSS_RELAXATION
325     interp_method=2
326     call exf_init_gen (
327     & climsssfile, climsssperiod, exf_inscal_climsss, climsssmask,
328     & climsssconst, climsss, climsss0, climsss1,
329     #ifdef USE_EXF_INTERPOLATION
330     & climsss_lon0, climsss_lon_inc,
331     & climsss_lat0, climsss_lat_inc,
332     & climsss_nlon, climsss_nlat, xC, yC, interp_method,
333     #endif
334     & mythid )
335     #endif
336    
337     c Initialize climatological fields
338     cph call exf_clim_init ( mythid )
339    
340     RETURN
341     END

  ViewVC Help
Powered by ViewVC 1.1.22