/[MITgcm]/MITgcm_contrib/ecco_darwin/v2_cs510_Brix/code/exf_init.F
ViewVC logotype

Annotation of /MITgcm_contrib/ecco_darwin/v2_cs510_Brix/code/exf_init.F

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


Revision 1.1 - (hide annotations) (download)
Tue Aug 28 14:59:05 2018 UTC (6 years, 11 months ago) by dimitri
Branch: MAIN
initial check-in of v2_cs510_Brix
right now it is a shell that is identical to v3_cs510_Brix
we will modify it to match the Brix et al 2015 v2 solution

1 dimitri 1.1 C $Header: /u/gcmpack/MITgcm_contrib/ecco_darwin/v3_cs510_Brix/code/exf_init.F,v 1.1 2017/11/28 19:50:42 dimitri 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     #ifdef ALLOW_BULK_OFFLINE
33     # include "PARAMS.h"
34     # include "DYNVARS.h"
35     #endif
36    
37     c == routine arguments ==
38    
39     integer mythid
40    
41     c == local variables ==
42    
43     integer interp_method
44     INTEGER i,j,bi,bj
45    
46     c == end of interface ==
47    
48     C-- Initialise to zero intermediate fields (in common block)
49     DO bj = myByLo(myThid), myByHi(myThid)
50     DO bi = myBxLo(myThid), myBxHi(myThid)
51     DO j=1-Oly,sNy+Oly
52     DO i=1-Olx,sNx+Olx
53     wStress(i,j,bi,bj) = 0.
54     cw(i,j,bi,bj) = 0.
55     sw(i,j,bi,bj) = 0.
56     sh(i,j,bi,bj) = 0.
57     #ifdef ALLOW_ATM_TEMP
58     hs(i,j,bi,bj) = 0.
59     hl(i,j,bi,bj) = 0.
60     #endif
61     ENDDO
62     ENDDO
63     ENDDO
64     ENDDO
65    
66     if ( useCubedSphereExchange
67     & .and. ustressperiod .eq. 0
68     & .and. ustressfile .NE. ' ' ) then
69     stop 'CubedSphereExchange and ustressperiod=0 not supported'
70     endif
71     interp_method=12
72     call exf_init_gen (
73     & ustressfile, ustressperiod, exf_inscal_ustress, ustressmask,
74     & ustressconst, ustress, ustress0, ustress1,
75     #ifdef USE_EXF_INTERPOLATION
76     & ustress_lon0, ustress_lon_inc,
77     & ustress_lat0, ustress_lat_inc,
78     & ustress_nlon, ustress_nlat, xC, yC, interp_method,
79     #endif
80     & mythid )
81    
82     if ( useCubedSphereExchange
83     & .and. vstressperiod .eq. 0
84     & .and. vstressfile .NE. ' ' ) then
85     stop 'CubedSphereExchange and vstressperiod=0 not supported'
86     endif
87     interp_method=22
88     call exf_init_gen (
89     & vstressfile, vstressperiod, exf_inscal_vstress, vstressmask,
90     & vstressconst, vstress, vstress0, vstress1,
91     #ifdef USE_EXF_INTERPOLATION
92     & vstress_lon0, vstress_lon_inc,
93     & vstress_lat0, vstress_lat_inc,
94     & vstress_nlon, vstress_nlat, xC, yC, interp_method,
95     #endif
96     & mythid )
97    
98     #ifdef ALLOW_ATM_WIND
99    
100     if ( useCubedSphereExchange
101     & .and. uwindperiod .eq. 0
102     & .and. uwindfile .NE. ' ' ) then
103     stop 'CubedSphereExchange and uwindperiod=0 not supported'
104     endif
105     interp_method=12
106     call exf_init_gen (
107     & uwindfile, uwindperiod, exf_inscal_uwind, uwindmask,
108     & uwindconst, uwind, uwind0, uwind1,
109     #ifdef USE_EXF_INTERPOLATION
110     & uwind_lon0, uwind_lon_inc,
111     & uwind_lat0, uwind_lat_inc,
112     & uwind_nlon, uwind_nlat, xC, yC, interp_method,
113     #endif
114     & mythid )
115    
116     if ( useCubedSphereExchange
117     & .and. vwindperiod .eq. 0
118     & .and. vwindfile .NE. ' ' ) then
119     stop 'CubedSphereExchange and vwindperiod=0 not supported'
120     endif
121     interp_method=22
122     call exf_init_gen (
123     & vwindfile, vwindperiod, exf_inscal_vwind, vwindmask,
124     & vwindconst, vwind, vwind0, vwind1,
125     #ifdef USE_EXF_INTERPOLATION
126     & vwind_lon0, vwind_lon_inc,
127     & vwind_lat0, vwind_lat_inc,
128     & vwind_nlon, vwind_nlat, xC, yC, interp_method,
129     #endif
130     & mythid )
131    
132     #endif /* ALLOW_ATM_WIND */
133    
134     interp_method=1
135    
136     call exf_init_gen (
137     & wspeedfile, wspeedperiod, exf_inscal_wspeed, wspeedmask,
138     & wspeedconst, wspeed, wspeed0, wspeed1,
139     #ifdef USE_EXF_INTERPOLATION
140     & wspeed_lon0, wspeed_lon_inc,
141     & wspeed_lat0, wspeed_lat_inc,
142     & wspeed_nlon, wspeed_nlat, xC, yC, interp_method,
143     #endif
144     & mythid )
145    
146     call exf_init_gen (
147     & hfluxfile, hfluxperiod, exf_inscal_hflux, hfluxmask,
148     & hfluxconst, hflux, hflux0, hflux1,
149     #ifdef USE_EXF_INTERPOLATION
150     & hflux_lon0, hflux_lon_inc,
151     & hflux_lat0, hflux_lat_inc,
152     & hflux_nlon, hflux_nlat, xC, yC, interp_method,
153     #endif
154     & mythid )
155    
156     call exf_init_gen (
157     & sfluxfile, sfluxperiod, exf_inscal_sflux, sfluxmask,
158     & sfluxconst, sflux, sflux0, sflux1,
159     #ifdef USE_EXF_INTERPOLATION
160     & sflux_lon0, sflux_lon_inc,
161     & sflux_lat0, sflux_lat_inc,
162     & sflux_nlon, sflux_nlat, xC, yC, interp_method,
163     #endif
164     & mythid )
165    
166     #ifdef ALLOW_ATM_TEMP
167    
168     call exf_init_gen (
169     & atempfile, atempperiod, exf_inscal_atemp, atempmask,
170     & atempconst, atemp, atemp0, atemp1,
171     #ifdef USE_EXF_INTERPOLATION
172     & atemp_lon0, atemp_lon_inc,
173     & atemp_lat0, atemp_lat_inc,
174     & atemp_nlon, atemp_nlat, xC, yC, interp_method,
175     #endif
176     & mythid )
177    
178     call exf_init_gen (
179     & aqhfile, aqhperiod, exf_inscal_aqh, aqhmask,
180     & aqhconst, aqh, aqh0, aqh1,
181     #ifdef USE_EXF_INTERPOLATION
182     & aqh_lon0, aqh_lon_inc,
183     & aqh_lat0, aqh_lat_inc,
184     & aqh_nlon, aqh_nlat, xC, yC, interp_method,
185     #endif
186     & mythid )
187    
188     call exf_init_gen (
189     & lwfluxfile, lwfluxperiod, exf_inscal_lwflux, lwfluxmask,
190     & lwfluxconst, lwflux, lwflux0, lwflux1,
191     #ifdef USE_EXF_INTERPOLATION
192     & lwflux_lon0, lwflux_lon_inc,
193     & lwflux_lat0, lwflux_lat_inc,
194     & lwflux_nlon, lwflux_nlat, xC, yC, interp_method,
195     #endif
196     & mythid )
197    
198     call exf_init_gen (
199     & precipfile, precipperiod, exf_inscal_precip, precipmask,
200     & precipconst, precip, precip0, precip1,
201     #ifdef USE_EXF_INTERPOLATION
202     & precip_lon0, precip_lon_inc,
203     & precip_lat0, precip_lat_inc,
204     & precip_nlon, precip_nlat, xC, yC, interp_method,
205     #endif
206     & mythid )
207    
208     call exf_init_gen (
209     & snowprecipfile, snowprecipperiod,
210     & exf_inscal_snowprecip, snowprecipmask,
211     & snowprecipconst, snowprecip, snowprecip0, snowprecip1,
212     #ifdef USE_EXF_INTERPOLATION
213     & snowprecip_lon0, snowprecip_lon_inc,
214     & snowprecip_lat0, snowprecip_lat_inc,
215     & snowprecip_nlon, snowprecip_nlat, xC, yC, interp_method,
216     #endif
217     & mythid )
218    
219     #endif /* ALLOW_ATM_TEMP */
220    
221     #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
222     call exf_init_gen (
223     & swfluxfile, swfluxperiod, exf_inscal_swflux, swfluxmask,
224     & swfluxconst, swflux, swflux0, swflux1,
225     #ifdef USE_EXF_INTERPOLATION
226     & swflux_lon0, swflux_lon_inc,
227     & swflux_lat0, swflux_lat_inc,
228     & swflux_nlon, swflux_nlat, xC, yC, interp_method,
229     #endif
230     & mythid )
231     #endif /* defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING) */
232    
233     #if defined(ALLOW_ATM_TEMP) || defined(EXF_READ_EVAP)
234     call exf_init_gen (
235     & evapfile, evapperiod, exf_inscal_evap, evapmask,
236     & evapconst, evap, evap0, evap1,
237     #ifdef USE_EXF_INTERPOLATION
238     & evap_lon0, evap_lon_inc,
239     & evap_lat0, evap_lat_inc,
240     & evap_nlon, evap_nlat, xC, yC, interp_method,
241     #endif
242     & mythid )
243     #endif /* defined(ALLOW_ATM_TEMP) || defined(EXF_READ_EVAP) */
244    
245     #ifdef ALLOW_DOWNWARD_RADIATION
246    
247     call exf_init_gen (
248     & swdownfile, swdownperiod, exf_inscal_swdown, swdownmask,
249     & swdownconst, swdown, swdown0, swdown1,
250     #ifdef USE_EXF_INTERPOLATION
251     & swdown_lon0, swdown_lon_inc,
252     & swdown_lat0, swdown_lat_inc,
253     & swdown_nlon, swdown_nlat, xC, yC, interp_method,
254     #endif
255     & mythid )
256    
257     call exf_init_gen (
258     & lwdownfile, lwdownperiod, exf_inscal_lwdown, lwdownmask,
259     & lwdownconst, lwdown, lwdown0, lwdown1,
260     #ifdef USE_EXF_INTERPOLATION
261     & lwdown_lon0, lwdown_lon_inc,
262     & lwdown_lat0, lwdown_lat_inc,
263     & lwdown_nlon, lwdown_nlat, xC, yC, interp_method,
264     #endif
265     & mythid )
266    
267     #endif /* ALLOW_DOWNWARD_RADIATION */
268    
269     #ifdef ATMOSPHERIC_LOADING
270     call exf_init_gen (
271     & apressurefile, apressureperiod,
272     & exf_inscal_apressure, apressuremask,
273     & apressureconst, apressure, apressure0, apressure1,
274     #ifdef USE_EXF_INTERPOLATION
275     & apressure_lon0, apressure_lon_inc,
276     & apressure_lat0, apressure_lat_inc,
277     & apressure_nlon, apressure_nlat, xC, yC, interp_method,
278     #endif
279     & mythid )
280     #endif /* ATMOSPHERIC_LOADING */
281    
282     #ifdef ALLOW_ICE_AREAMASK
283     call exf_init_gen (
284     & areamaskfile, areamaskperiod,
285     & exf_inscal_areamask, areamaskmask,
286     & areamaskconst, areamask, areamask0, areamask1,
287     #ifdef USE_EXF_INTERPOLATION
288     & areamask_lon0, areamask_lon_inc,
289     & areamask_lat0, areamask_lat_inc,
290     & areamask_nlon, areamask_nlat, xC, yC, interp_method,
291     #endif
292     & mythid )
293     #endif /* ALLOW_ICE_AREAMASK */
294    
295     #ifdef ALLOW_RUNOFF
296     #ifdef USE_NO_INTERP_RUNOFF
297     call exf_init_runoff (
298     & runofffile, runoffperiod, exf_inscal_runoff, runoffmask,
299     & runoffconst, runoff, runoff0, runoff1,
300     & mythid )
301     #else /* ndef USE_NO_INTERP_RUNOFF */
302     call exf_init_gen (
303     & runofffile, runoffperiod, exf_inscal_runoff, runoffmask,
304     & runoffconst, runoff, runoff0, runoff1,
305     #ifdef USE_EXF_INTERPOLATION
306     & runoff_lon0, runoff_lon_inc,
307     & runoff_lat0, runoff_lat_inc,
308     & runoff_nlon, runoff_nlat, xC, yC, interp_method,
309     #endif
310     & mythid )
311     #endif /* def USE_NO_INTERP_RUNOFF */
312     #endif /* ALLOW_RUNOFF */
313    
314     #ifdef ALLOW_CLIMSST_RELAXATION
315     interp_method=2
316     call exf_init_gen (
317     & climsstfile, climsstperiod, exf_inscal_climsst, climsstmask,
318     & climsstconst, climsst, climsst0, climsst1,
319     #ifdef USE_EXF_INTERPOLATION
320     & climsst_lon0, climsst_lon_inc,
321     & climsst_lat0, climsst_lat_inc,
322     & climsst_nlon, climsst_nlat, xC, yC, interp_method,
323     #endif
324     & mythid )
325     #endif
326    
327     #ifdef ALLOW_CLIMSSS_RELAXATION
328     interp_method=2
329     call exf_init_gen (
330     & climsssfile, climsssperiod, exf_inscal_climsss, climsssmask,
331     & climsssconst, climsss, climsss0, climsss1,
332     #ifdef USE_EXF_INTERPOLATION
333     & climsss_lon0, climsss_lon_inc,
334     & climsss_lat0, climsss_lat_inc,
335     & climsss_nlon, climsss_nlat, xC, yC, interp_method,
336     #endif
337     & mythid )
338     #endif
339    
340     #ifdef ALLOW_CLIMSTRESS_RELAXATION
341     interp_method=12
342     call exf_init_gen (
343     & climustrfile, climustrperiod, exf_inscal_climustr,
344     & climustrmask, climustrconst, climustr, climustr0, climustr1,
345     #ifdef USE_EXF_INTERPOLATION
346     & climustr_lon0, climustr_lon_inc,
347     & climustr_lat0, climustr_lat_inc,
348     & climustr_nlon, climustr_nlat, xC, yC, interp_method,
349     #endif
350     & mythid )
351     c
352     interp_method=22
353     call exf_init_gen (
354     & climvstrfile, climvstrperiod, exf_inscal_climvstr,
355     & climvstrmask, climvstrconst, climvstr, climvstr0, climvstr1,
356     #ifdef USE_EXF_INTERPOLATION
357     & climvstr_lon0, climvstr_lon_inc,
358     & climvstr_lat0, climvstr_lat_inc,
359     & climvstr_nlon, climvstr_nlat, xC, yC, interp_method,
360     #endif
361     & mythid )
362     #endif /* CLIMSTRESS_RELAXATION */
363    
364     #ifdef ALLOW_BULK_OFFLINE
365    
366     # ifdef ALLOW_CLIMSST_RELAXATION
367     _EXCH_XY_RL(climsst, mythid)
368     # endif
369     # ifdef ALLOW_CLIMSSS_RELAXATION
370     _EXCH_XY_RL(climsss, mythid)
371     # endif
372     # ifdef ALLOW_CLIMSTRESS_RELAXATION
373     CALL EXCH_UV_XY_RL( climustr, climvstr, .TRUE., myThid )
374     # endif
375    
376     DO bj=myByLo(myThid),myByHi(myThid)
377     DO bi=myBxLo(myThid),myBxHi(myThid)
378     DO j=1-oLy,sNy+oLy
379     DO i=1-oLx,sNx+oLx
380     # ifdef ALLOW_CLIMSST_RELAXATION
381     if ( climsstfile .NE. ' ' .AND.
382     & climsstperiod .EQ. 0. )
383     & theta(i,j,1,bi,bj) = climsst(i,j,bi,bj)
384     # endif
385     # ifdef ALLOW_CLIMSSS_RELAXATION
386     if ( climsssfile .NE. ' ' .AND.
387     & climsssperiod .EQ. 0. )
388     & salt(i,j,1,bi,bj) = climsss(i,j,bi,bj)
389     # endif
390     # ifdef ALLOW_CLIMSTRESS_RELAXATION
391     if ( climustrfile .NE. ' ' .AND.
392     & climustrperiod .EQ. 0. )
393     & uvel(i,j,1,bi,bj) = climustr(i,j,bi,bj)
394     if ( climvstrfile .NE. ' ' .AND.
395     & climvstrperiod .EQ. 0. )
396     & vvel(i,j,1,bi,bj) = climvstr(i,j,bi,bj)
397     # endif
398     if ( maskC(i,j,1,bi,bj) .NE. 0. .AND.
399     & theta(i,j,1,bi,bj) .EQ. 0. ) then
400     print *, 'ph-warn-exf-init ', i, j, theta(i,j,1,bi,bj)
401     cph STOP 'in exf_init'
402     endif
403     ENDDO
404     ENDDO
405     ENDDO
406     ENDDO
407    
408     #endif /* ALLOW_BULK_OFFLINE */
409    
410     #ifdef ALLOW_CARBON
411     #ifdef USE_EXFCO2
412     call exf_init_gen (
413     & apco2file, apco2period, exf_inscal_apco2, apco2mask,
414     & apco2const, apco2, apco20, apco21,
415     # ifdef USE_EXF_INTERPOLATION
416     & apco2_lon0, apco2_lon_inc,
417     & apco2_lat0, apco2_lat_inc,
418     & apco2_nlon, apco2_nlat, xC, yC, interp_method,
419     # endif
420     & mythid )
421     #endif
422     #endif
423    
424     RETURN
425     END

  ViewVC Help
Powered by ViewVC 1.1.22