/[MITgcm]/MITgcm_contrib/dcarroll/highres_darwin/code/exf_readparms.F
ViewVC logotype

Annotation of /MITgcm_contrib/dcarroll/highres_darwin/code/exf_readparms.F

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


Revision 1.1 - (hide annotations) (download)
Sun Sep 22 21:23:46 2019 UTC (5 years, 10 months ago) by dcarroll
Branch: MAIN
CVS Tags: HEAD
Initial check in of high resolution Darwin simulation code

1 dcarroll 1.1 C $Header: /u/gcmpack/MITgcm_contrib/ecco_darwin/v4_llc270/code_darwin/exf_readparms.F,v 1.1 2017/12/01 19:02:11 dimitri Exp $
2     C $Name: $
3    
4     #include "EXF_OPTIONS.h"
5     #ifdef ALLOW_EXCH2
6     # include "W2_OPTIONS.h"
7     #endif /* ALLOW_EXCH2 */
8    
9     SUBROUTINE EXF_READPARMS( myThid )
10    
11     C ==================================================================
12     C SUBROUTINE exf_readparms
13     C ==================================================================
14     C
15     C o This routine initialises the package that calculates external
16     C forcing fields for a given timestep of the MITgcmUV. Parameters
17     C for this package are set in "data.externalforcing". Some additional
18     C precompiler switches have to be specified in "EXF_OPTIONS.h".
19     C
20     C started: Christian Eckert eckert@mit.edu 30-Jun-1999
21     C
22     C changed: Christian Eckert eckert@mit.edu 11-Jan-2000
23     C - Restructured the code in order to create a package
24     C for the MITgcmUV.
25     C Christian Eckert eckert@mit.edu 12-Feb-2000
26     C - Changed Routine names (package prefix: exf_)
27     C changed: Patrick Heimbach, heimbach@mit.edu 04-May-2000
28     C - changed the handling of precip and sflux with respect
29     C to CPP options ALLOW_BULKFORMULAE and ALLOW_ATM_TEMP
30     C changed: Ralf.Giering@FastOpt.de 25-Mai-20000
31     C - moved relaxation and climatology to extra routines
32     C Patrick Heimbach, heimbach@mit.edu 04-May-2000
33     C - added obcs parameters
34     C changed: Virginie Thierry, vthierry@ucsd.edu 04-June-2001
35     C - added new obcs parameters (for each boundaries)
36     C included runoff D. Stammer, Nov. 25, 2001
37     C included pressure forcing. heimbach@mit.edu 05-Nov-2002
38     C added "repeatPeriod" for cycling of forcing datasets 19-Dec-2002
39     C mods for pkg/seaice: menemenlis@jpl.nasa.gov 20-Dec-2002
40     C
41     C ==================================================================
42     C SUBROUTINE exf_readparms
43     C ==================================================================
44    
45     implicit none
46    
47     C == global variables ==
48    
49     #include "EEPARAMS.h"
50     #include "SIZE.h"
51     #include "PARAMS.h"
52     #ifdef USE_EXF_INTERPOLATION
53     # ifdef ALLOW_EXCH2
54     # include "W2_EXCH2_SIZE.h"
55     # include "W2_EXCH2_TOPOLOGY.h"
56     # endif /* ALLOW_EXCH2 */
57     # include "SET_GRID.h"
58     #endif /* USE_EXF_INTERPOLATION */
59     c#include "cal.h"
60     #include "EXF_PARAM.h"
61     #include "EXF_CONSTANTS.h"
62    
63     C == routine arguments ==
64     INTEGER myThid
65    
66     C == local variables ==
67     #ifdef USE_EXF_INTERPOLATION
68     INTEGER gridNx, gridNy
69     INTEGER j
70     _RL inp_lon0, inp_lat0, inp_dLon, inp_dLat
71     #endif /* USE_EXF_INTERPOLATION */
72     INTEGER iUnit
73     LOGICAL exf_verbose
74     CHARACTER*(2) exf_yftype
75     CHARACTER*(MAX_LEN_MBUF) msgBuf
76     _RL exf_inscal_sst, exf_inscal_sss
77     C == end of interface ==
78    
79     C Surface flux data.
80     NAMELIST /EXF_NML_01/
81     & windstressmax, repeatPeriod, exf_albedo,
82     & ocean_emissivity, ice_emissivity, snow_emissivity,
83     & exf_iceCd, exf_iceCe, exf_iceCh,
84     & exf_scal_BulkCdn, climtempfreeze, useExfCheckRange,
85     & exf_iprec , exf_iprec_obcs , exf_yftype,
86     & exf_verbose , exf_debugLev , exf_monFreq,
87     & useExfYearlyFields, twoDigitYear,
88     & useStabilityFct_overIce, readStressOnAgrid, readStressOnCgrid,
89     & rotateStressOnAgrid, useAtmWind, useRelativeWind, noNegativeEvap,
90     & select_ZenAlbedo, useExfZenIncoming,
91     & hu, ht, umin, atmrho, atmcp, cen2kel, gravity_mks,
92     & cdrag_1, cdrag_2, cdrag_3, cstanton_1, cstanton_2, cdalton,
93     & flamb, flami, zolmin, zref,
94     & cvapor_fac, cvapor_exp, cvapor_fac_ice, cvapor_exp_ice,
95     & humid_fac, gamma_blk, saltsat, sstExtrapol, psim_fac
96    
97     NAMELIST /EXF_NML_02/
98     & hfluxfile, hfluxstartdate1, hfluxstartdate2,
99     & hfluxRepCycle, hfluxperiod, hfluxStartTime,
100     & atempfile, atempstartdate1, atempstartdate2,
101     & atempRepCycle, atempperiod, atempStartTime,
102     & aqhfile, aqhstartdate1, aqhstartdate2,
103     & aqhRepCycle, aqhperiod, aqhStartTime,
104     & hs_file, hs_startdate1, hs_startdate2,
105     & hs_RepCycle, hs_period, hs_StartTime,
106     & hl_file, hl_startdate1, hl_startdate2,
107     & hl_RepCycle, hl_period, hl_StartTime,
108     & sfluxfile, sfluxstartdate1, sfluxstartdate2,
109     & sfluxRepCycle, sfluxperiod, sfluxStartTime,
110     & evapfile, evapstartdate1, evapstartdate2,
111     & evapRepCycle, evapperiod, evapStartTime,
112     & precipfile, precipstartdate1, precipstartdate2,
113     & precipRepCycle, precipperiod, precipStartTime,
114     & snowprecipfile, snowprecipstartdate1, snowprecipstartdate2,
115     & snowprecipRepCycle, snowprecipperiod, snowprecipStartTime,
116     & runofffile, runoffstartdate1, runoffstartdate2,
117     & runoffRepCycle, runoffperiod, runoffStartTime,
118     & runoftempfile,
119     & saltflxfile, saltflxstartdate1, saltflxstartdate2,
120     & saltflxRepCycle, saltflxperiod, saltflxStartTime,
121     & ustressfile, ustressstartdate1, ustressstartdate2,
122     & ustressRepCycle, ustressperiod, ustressStartTime,
123     & vstressfile, vstressstartdate1, vstressstartdate2,
124     & vstressRepCycle, vstressperiod, vstressStartTime,
125     & uwindfile, uwindstartdate1, uwindstartdate2,
126     & uwindRepCycle, uwindperiod, uwindStartTime,
127     & vwindfile, vwindstartdate1, vwindstartdate2,
128     & vwindRepCycle, vwindperiod, vwindStartTime,
129     & wspeedfile, wspeedstartdate1, wspeedstartdate2,
130     & wspeedRepCycle, wspeedperiod, wspeedStartTime,
131     & swfluxfile, swfluxstartdate1, swfluxstartdate2,
132     & swfluxRepCycle, swfluxperiod, swfluxStartTime,
133     & lwfluxfile, lwfluxstartdate1, lwfluxstartdate2,
134     & lwfluxRepCycle, lwfluxperiod, lwfluxStartTime,
135     & swdownfile, swdownstartdate1, swdownstartdate2,
136     & swdownRepCycle, swdownperiod, swdownStartTime,
137     & lwdownfile, lwdownstartdate1, lwdownstartdate2,
138     & lwdownRepCycle, lwdownperiod, lwdownStartTime,
139     & apressurefile, apressurestartdate1, apressurestartdate2,
140     & apressureRepCycle, apressureperiod, apressureStartTime,
141     & tidePotFile, tidePotStartdate1, tidePotStartdate2,
142     & tidePotRepCycle, tidePotPeriod, tidePotStartTime,
143     & areamaskfile, areamaskstartdate1, areamaskstartdate2,
144     & areamaskRepCycle, areamaskperiod, areamaskStartTime,
145     & climsstfile, climsststartdate1, climsststartdate2,
146     & climsstRepCycle, climsstperiod, climsstStartTime,
147     & climsssfile, climsssstartdate1, climsssstartdate2,
148     & climsssRepCycle, climsssperiod, climsssStartTime,
149     & climustrfile, climustrstartdate1, climustrstartdate2,
150     & climustrRepCycle, climustrperiod, climustrStartTime,
151     & climvstrfile, climvstrstartdate1, climvstrstartdate2,
152     & climvstrRepCycle, climvstrperiod, climvstrStartTime,
153     & areamaskTauRelax, climsstTauRelax, climsssTauRelax,
154     & climustrTauRelax, climvstrTauRelax,
155     & apco2file, apco2startdate1, apco2startdate2,
156     & apco2RepCycle, apco2period, apco2StartTime
157    
158     NAMELIST /EXF_NML_03/
159     & exf_inscal_hflux, exf_inscal_sflux, exf_inscal_evap,
160     & exf_inscal_ustress, exf_inscal_vstress,
161     & exf_inscal_uwind, exf_inscal_vwind, exf_inscal_wspeed,
162     & exf_inscal_atemp, exf_offset_atemp,
163     & exf_inscal_aqh, exf_inscal_hs, exf_inscal_hl,
164     & exf_inscal_sst, exf_inscal_sss,
165     & exf_inscal_swflux, exf_inscal_lwflux, exf_inscal_precip,
166     & exf_inscal_runoff, exf_inscal_apressure, exf_inscal_snowprecip,
167     & exf_inscal_runoftemp, exf_inscal_saltflx,
168     & exf_inscal_swdown, exf_inscal_lwdown,
169     & exf_inscal_climsst, exf_inscal_climsss,
170     & exf_inscal_climustr, exf_inscal_climvstr,
171     & exf_outscal_hflux, exf_outscal_ustress, exf_outscal_vstress,
172     & exf_outscal_swflux, exf_outscal_sst, exf_outscal_sss,
173     & exf_outscal_sflux, exf_outscal_apressure,
174     & exf_inscal_tidePot, exf_outscal_tidePot,
175     & exf_inscal_areamask, exf_outscal_areamask,
176     & hfluxconst, atempconst, aqhconst, hs_const, hl_const,
177     & sfluxconst, evapconst, precipconst, snowprecipconst,
178     & runoffconst, runoftempconst, saltflxconst, ustressconst,
179     & vstressconst, uwindconst, vwindconst, wspeedconst, swfluxconst,
180     & lwfluxconst, swdownconst, lwdownconst, apressureconst,
181     & tidePotConst, areamaskconst, climsstconst, climsssconst,
182     & climustrconst, climvstrconst,
183     & hflux_exfremo_intercept, hflux_exfremo_slope,
184     & atemp_exfremo_intercept, atemp_exfremo_slope,
185     & aqh_exfremo_intercept, aqh_exfremo_slope,
186     & hs_exfremo_intercept, hs_exfremo_slope,
187     & hl_exfremo_intercept, hl_exfremo_slope,
188     & sflux_exfremo_intercept, sflux_exfremo_slope,
189     & evap_exfremo_intercept, evap_exfremo_slope,
190     & precip_exfremo_intercept, precip_exfremo_slope,
191     & snowprecip_exfremo_intercept, snowprecip_exfremo_slope,
192     & runoff_exfremo_intercept, runoff_exfremo_slope,
193     & runoftemp_exfremo_intercept, runoftemp_exfremo_slope,
194     & saltflx_exfremo_intercept, saltflx_exfremo_slope,
195     & ustress_exfremo_intercept, ustress_exfremo_slope,
196     & vstress_exfremo_intercept, vstress_exfremo_slope,
197     & uwind_exfremo_intercept, uwind_exfremo_slope,
198     & vwind_exfremo_intercept, vwind_exfremo_slope,
199     & wspeed_exfremo_intercept, wspeed_exfremo_slope,
200     & swflux_exfremo_intercept, swflux_exfremo_slope,
201     & lwflux_exfremo_intercept, lwflux_exfremo_slope,
202     & swdown_exfremo_intercept, swdown_exfremo_slope,
203     & lwdown_exfremo_intercept, lwdown_exfremo_slope,
204     & apressure_exfremo_intercept, apressure_exfremo_slope,
205     & tidePot_exfremo_intercept, tidePot_exfremo_slope,
206     & areamask_exfremo_intercept, areamask_exfremo_slope,
207     & climsst_exfremo_intercept, climsst_exfremo_slope,
208     & climsss_exfremo_intercept, climsss_exfremo_slope,
209     & climustr_exfremo_intercept, climustr_exfremo_slope,
210     & climvstr_exfremo_intercept, climvstr_exfremo_slope,
211     & exf_inscal_apco2,exf_outscal_apco2, apco2const,
212     & apco2_exfremo_intercept, apco2_exfremo_slope
213    
214     #ifdef USE_EXF_INTERPOLATION
215     NAMELIST /EXF_NML_04/
216     & ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
217     & ustress_nlon, ustress_nlat, ustress_interpMethod,
218     & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
219     & vstress_nlon, vstress_nlat, vstress_interpMethod,
220     & hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
221     & hflux_nlon, hflux_nlat, hflux_interpMethod,
222     & sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
223     & sflux_nlon, sflux_nlat, sflux_interpMethod,
224     & swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
225     & swflux_nlon, swflux_nlat, swflux_interpMethod,
226     & lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
227     & lwflux_nlon, lwflux_nlat, lwflux_interpMethod,
228     & atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
229     & atemp_nlon, atemp_nlat, atemp_interpMethod,
230     & aqh_lon0, aqh_lon_inc, aqh_lat0, aqh_lat_inc,
231     & aqh_nlon, aqh_nlat, aqh_interpMethod,
232     & hs_lon0, hs_lon_inc, hs_lat0, hs_lat_inc,
233     & hs_nlon, hs_nlat, hs_interpMethod,
234     & hl_lon0, hl_lon_inc, hl_lat0, hl_lat_inc,
235     & hl_nlon, hl_nlat, hl_interpMethod,
236     & evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
237     & evap_nlon, evap_nlat, evap_interpMethod,
238     & precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
239     & precip_nlon, precip_nlat, precip_interpMethod,
240     & runoff_lon0, runoff_lon_inc, runoff_lat0, runoff_lat_inc,
241     & runoff_nlon, runoff_nlat, runoff_interpMethod,
242     & saltflx_lon0, saltflx_lon_inc,
243     & saltflx_lat0, saltflx_lat_inc,
244     & saltflx_nlon, saltflx_nlat, saltflx_interpMethod,
245     & snowprecip_lon0, snowprecip_lon_inc,
246     & snowprecip_lat0, snowprecip_lat_inc,
247     & snowprecip_nlon, snowprecip_nlat, snowprecip_interpMethod,
248     & uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
249     & uwind_nlon, uwind_nlat, uwind_interpMethod,
250     & vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
251     & vwind_nlon, vwind_nlat, vwind_interpMethod,
252     & wspeed_lon0, wspeed_lon_inc, wspeed_lat0, wspeed_lat_inc,
253     & wspeed_nlon, wspeed_nlat, wspeed_interpMethod,
254     & swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
255     & swdown_nlon, swdown_nlat, swdown_interpMethod,
256     & lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
257     & lwdown_nlon, lwdown_nlat, lwdown_interpMethod,
258     & apressure_lon0, apressure_lon_inc,
259     & apressure_lat0, apressure_lat_inc,
260     & apressure_nlon, apressure_nlat, apressure_interpMethod,
261     & tidePot_lon0, tidePot_lon_inc, tidePot_lat0, tidePot_lat_inc,
262     & tidePot_nlon, tidePot_nlat, tidePot_interpMethod,
263     & areamask_lon0, areamask_lon_inc, areamask_lat0, areamask_lat_inc,
264     & areamask_nlon, areamask_nlat, areamask_interpMethod,
265     & climsst_lon0, climsst_lon_inc, climsst_lat0, climsst_lat_inc,
266     & climsst_nlon, climsst_nlat, climsst_interpMethod,
267     & climsss_lon0, climsss_lon_inc,climsss_lat0, climsss_lat_inc,
268     & climsss_nlon, climsss_nlat, climsss_interpMethod,
269     & climustr_lon0, climustr_lon_inc, climustr_lat0, climustr_lat_inc,
270     & climustr_nlon, climustr_nlat, climustr_interpMethod,
271     & climvstr_lon0, climvstr_lon_inc, climvstr_lat0, climvstr_lat_inc,
272     & climvstr_nlon, climvstr_nlat, climvstr_interpMethod,
273     & exf_output_interp,
274     & apco2_lon0, apco2_lon_inc, apco2_lat0, apco2_lat_inc,
275     & apco2_nlon, apco2_nlat, apco2_interpMethod
276     #endif /* USE_EXF_INTERPOLATION */
277    
278     #ifdef ALLOW_OBCS
279     NAMELIST /EXF_NML_OBCS/
280     & useOBCSYearlyFields,
281     & obcsNstartdate1, obcsNstartdate2, obcsNstartTime,
282     & obcsNperiod, obcsNrepCycle,
283     & obcsSstartdate1, obcsSstartdate2, obcsSstartTime,
284     & obcsSperiod, obcsSrepCycle,
285     & obcsEstartdate1, obcsEstartdate2, obcsEstartTime,
286     & obcsEperiod, obcsErepCycle,
287     & obcsWstartdate1, obcsWstartdate2, obcsWstartTime,
288     & obcsWperiod, obcsWrepCycle,
289     & siobNstartdate1, siobNstartdate2, siobNstartTime,
290     & siobNperiod, siobNrepCycle,
291     & siobSstartdate1, siobSstartdate2, siobSstartTime,
292     & siobSperiod, siobSrepCycle,
293     & siobEstartdate1, siobEstartdate2, siobEstartTime,
294     & siobEperiod, siobErepCycle,
295     & siobWstartdate1, siobWstartdate2, siobWstartTime,
296     & siobWperiod, siobWrepCycle
297     #endif /* ALLOW_OBCS */
298    
299     #ifdef USE_EXF_INTERPOLATION
300     # ifdef ALLOW_EXCH2
301     gridNx = exch2_mydNx(1)
302     gridNy = exch2_mydNy(1)
303     # else /* ALLOW_EXCH2 */
304     gridNx = Nx
305     gridNy = Ny
306     # endif /* ALLOW_EXCH2 */
307     #endif /* USE_EXF_INTERPOLATION */
308    
309     IF ( .NOT.useEXF ) THEN
310     C- pkg EXF is not used
311     _BEGIN_MASTER(myThid)
312     C- Track pkg activation status:
313     C print a (weak) warning if data.exf is found
314     CALL PACKAGES_UNUSED_MSG( 'useEXF', ' ', ' ' )
315     _END_MASTER(myThid)
316     RETURN
317     ENDIF
318    
319     _BEGIN_MASTER(myThid)
320    
321     C Set default values.
322    
323     c exf_verbose = debugMode
324     exf_verbose = .FALSE.
325     exf_debugLev = debugLevel
326     exf_monFreq = monitorFreq
327     useExfCheckRange = .TRUE.
328     select_ZenAlbedo = 0
329     useExfZenIncoming = .FALSE.
330     readStressOnAgrid = .FALSE.
331     rotateStressOnAgrid = .FALSE.
332     readStressOnCgrid = .FALSE.
333     #ifdef ALLOW_ATM_WIND
334     useAtmWind = .TRUE.
335     #else
336     useAtmWind = .FALSE.
337     #endif
338     useRelativeWind = .FALSE.
339     noNegativeEvap = .FALSE.
340    
341     C- default value should be set to main model parameter:
342     c cen2kel = celsius2K
343     c gravity_mks = gravity
344     c atmcp = atm_Cp
345     c humid_fac = atm_Rq <- default is zero !!!
346    
347     cen2kel = 273.150 _d 0
348     gravity_mks = 9.81 _d 0
349     atmrho = 1.200 _d 0
350     atmcp = 1005.000 _d 0
351     flamb = 2500000.000 _d 0
352     flami = 334000.000 _d 0
353     cvapor_fac = 640380.000 _d 0
354     cvapor_exp = 5107.400 _d 0
355     cvapor_fac_ice = 11637800.000 _d 0
356     cvapor_exp_ice = 5897.800 _d 0
357     humid_fac = 0.606 _d 0
358     gamma_blk = 0.010 _d 0
359     saltsat = 0.980 _d 0
360     sstExtrapol = 0.0 _d 0
361     cdrag_1 = 0.0027000 _d 0
362     cdrag_2 = 0.0001420 _d 0
363     cdrag_3 = 0.0000764 _d 0
364     cstanton_1 = 0.0327 _d 0
365     cstanton_2 = 0.0180 _d 0
366     cdalton = 0.0346 _d 0
367     zolmin = -100.000 _d 0
368     psim_fac = 5.000 _d 0
369     zref = 10.000 _d 0
370     hu = 10.000 _d 0
371     ht = 2.000 _d 0
372     umin = 0.5 _d 0
373     useStabilityFct_overIce = .FALSE.
374     exf_iceCd = 1.63 _d -3
375     exf_iceCe = 1.63 _d -3
376     exf_iceCh = 1.63 _d -3
377     exf_albedo = 0.1 _d 0
378     C-- this default is chosen to be backward compatible with
379     C-- an earlier setting of 5.5 = ocean_emissivity*stefanBoltzmann
380     ocean_emissivity = 5.50 _d -8 / 5.670 _d -8
381     ice_emissivity = 0.95 _d 0
382     snow_emissivity = 0.95 _d 0
383    
384     C Calendar data.
385     hfluxstartdate1 = 0
386     hfluxstartdate2 = 0
387     hfluxperiod = 0.0 _d 0
388     hfluxconst = 0.0 _d 0
389     hflux_exfremo_intercept = 0.0 _d 0
390     hflux_exfremo_slope = 0.0 _d 0
391    
392     atempstartdate1 = 0
393     atempstartdate2 = 0
394     atempperiod = 0.0 _d 0
395     atempconst = celsius2K
396     atemp_exfremo_intercept = 0.0 _d 0
397     atemp_exfremo_slope = 0.0 _d 0
398    
399     aqhstartdate1 = 0
400     aqhstartdate2 = 0
401     aqhperiod = 0.0 _d 0
402     aqhconst = 0.0 _d 0
403     aqh_exfremo_intercept = 0.0 _d 0
404     aqh_exfremo_slope = 0.0 _d 0
405    
406     hs_startdate1 = 0
407     hs_startdate2 = 0
408     hs_period = 0.0 _d 0
409     hs_const = 0.0 _d 0
410     hs_exfremo_intercept = 0.0 _d 0
411     hs_exfremo_slope = 0.0 _d 0
412    
413     hl_startdate1 = 0
414     hl_startdate2 = 0
415     hl_period = 0.0 _d 0
416     hl_const = 0.0 _d 0
417     hl_exfremo_intercept = 0.0 _d 0
418     hl_exfremo_slope = 0.0 _d 0
419    
420     sfluxstartdate1 = 0
421     sfluxstartdate2 = 0
422     sfluxperiod = 0.0 _d 0
423     sfluxconst = 0.0 _d 0
424     sflux_exfremo_intercept = 0.0 _d 0
425     sflux_exfremo_slope = 0.0 _d 0
426    
427     evapstartdate1 = 0
428     evapstartdate2 = 0
429     evapperiod = 0.0 _d 0
430     evapconst = 0.0 _d 0
431     evap_exfremo_intercept = 0.0 _d 0
432     evap_exfremo_slope = 0.0 _d 0
433    
434     precipstartdate1 = 0
435     precipstartdate2 = 0
436     precipperiod = 0.0 _d 0
437     precipconst = 0.0 _d 0
438     precip_exfremo_intercept = 0.0 _d 0
439     precip_exfremo_slope = 0.0 _d 0
440    
441     snowprecipstartdate1 = 0
442     snowprecipstartdate2 = 0
443     snowprecipperiod = 0.0 _d 0
444     snowprecipconst = 0.0 _d 0
445     snowprecip_exfremo_intercept = 0.0 _d 0
446     snowprecip_exfremo_slope = 0.0 _d 0
447    
448     runoffstartdate1 = 0
449     runoffstartdate2 = 0
450     runoffperiod = 0.0 _d 0
451     runoffconst = 0.0 _d 0
452     runoff_exfremo_intercept = 0.0 _d 0
453     runoff_exfremo_slope = 0.0 _d 0
454    
455     runoftempconst = 0.0 _d 0
456     runoftemp_exfremo_intercept = 0.0 _d 0
457     runoftemp_exfremo_slope = 0.0 _d 0
458    
459     saltflxstartdate1 = 0
460     saltflxstartdate2 = 0
461     saltflxperiod = 0.0 _d 0
462     saltflxconst = 0.0 _d 0
463     saltflx_exfremo_intercept = 0.0 _d 0
464     saltflx_exfremo_slope = 0.0 _d 0
465    
466     ustressstartdate1 = 0
467     ustressstartdate2 = 0
468     ustressperiod = 0.0 _d 0
469     ustressconst = 0.0 _d 0
470     ustress_exfremo_intercept = 0.0 _d 0
471     ustress_exfremo_slope = 0.0 _d 0
472    
473     vstressstartdate1 = 0
474     vstressstartdate2 = 0
475     vstressperiod = 0.0 _d 0
476     vstressconst = 0.0 _d 0
477     vstress_exfremo_intercept = 0.0 _d 0
478     vstress_exfremo_slope = 0.0 _d 0
479    
480     uwindstartdate1 = 0
481     uwindstartdate2 = 0
482     uwindperiod = 0.0 _d 0
483     uwindconst = 0.0 _d 0
484     uwind_exfremo_intercept = 0.0 _d 0
485     uwind_exfremo_slope = 0.0 _d 0
486    
487     vwindstartdate1 = 0
488     vwindstartdate2 = 0
489     vwindperiod = 0.0 _d 0
490     vwindconst = 0.0 _d 0
491     vwind_exfremo_intercept = 0.0 _d 0
492     vwind_exfremo_slope = 0.0 _d 0
493    
494     wspeedstartdate1 = 0
495     wspeedstartdate2 = 0
496     wspeedperiod = 0.0 _d 0
497     wspeedconst = 0.0 _d 0
498     wspeed_exfremo_intercept = 0.0 _d 0
499     wspeed_exfremo_slope = 0.0 _d 0
500    
501     swfluxstartdate1 = 0
502     swfluxstartdate2 = 0
503     swfluxperiod = 0.0 _d 0
504     swfluxconst = 0.0 _d 0
505     swflux_exfremo_intercept = 0.0 _d 0
506     swflux_exfremo_slope = 0.0 _d 0
507    
508     lwfluxstartdate1 = 0
509     lwfluxstartdate2 = 0
510     lwfluxperiod = 0.0 _d 0
511     lwfluxconst = 0.0 _d 0
512     lwflux_exfremo_intercept = 0.0 _d 0
513     lwflux_exfremo_slope = 0.0 _d 0
514    
515     swdownstartdate1 = 0
516     swdownstartdate2 = 0
517     swdownperiod = 0.0 _d 0
518     swdownconst = 0.0 _d 0
519     swdown_exfremo_intercept = 0.0 _d 0
520     swdown_exfremo_slope = 0.0 _d 0
521    
522     lwdownstartdate1 = 0
523     lwdownstartdate2 = 0
524     lwdownperiod = 0.0 _d 0
525     lwdownconst = 0.0 _d 0
526     lwdown_exfremo_intercept = 0.0 _d 0
527     lwdown_exfremo_slope = 0.0 _d 0
528    
529     apressurestartdate1 = 0
530     apressurestartdate2 = 0
531     apressureperiod = 0.0 _d 0
532     apressureconst = 0.0 _d 0
533     apressure_exfremo_intercept = 0.0 _d 0
534     apressure_exfremo_slope = 0.0 _d 0
535    
536     tidePotStartdate1 = 0
537     tidePotStartdate2 = 0
538     tidePotPeriod = 0.0 _d 0
539     tidePotConst = 0.0 _d 0
540     tidePot_exfremo_intercept = 0. _d 0
541     tidePot_exfremo_slope = 0. _d 0
542    
543     apco2startdate1 = 0
544     apco2startdate2 = 0
545     apco2period = 0.0 _d 0
546     apco2const = 0.0 _d 0
547     apco2_exfremo_intercept = 0.0 _d 0
548     apco2_exfremo_slope = 0.0 _d 0
549    
550     areamaskstartdate1 = 0
551     areamaskstartdate2 = 0
552     areamaskperiod = 0.0 _d 0
553     areamaskTauRelax = 0.0 _d 0
554     areamaskconst = 0.0 _d 0
555     areamask_exfremo_intercept = 0. _d 0
556     areamask_exfremo_slope = 0. _d 0
557    
558     climsststartdate1 = 0
559     climsststartdate2 = 0
560     climsstperiod = 0
561     climsstTauRelax = 0.0 _d 0
562     climsstconst = 0.0 _d 0
563     climsst_exfremo_intercept = 0.0 _d 0
564     climsst_exfremo_slope = 0.0 _d 0
565    
566     climsssstartdate1 = 0
567     climsssstartdate2 = 0
568     climsssperiod = 0
569     climsssTauRelax = 0.0 _d 0
570     climsssconst = 0.0 _d 0
571     climsss_exfremo_intercept = 0.0 _d 0
572     climsss_exfremo_slope = 0.0 _d 0
573    
574     climustrstartdate1 = 0
575     climustrstartdate2 = 0
576     climustrperiod = 0
577     climustrTauRelax = 0.0 _d 0
578     climustrconst = 0.0 _d 0
579     climustr_exfremo_intercept = 0.0 _d 0
580     climustr_exfremo_slope = 0.0 _d 0
581    
582     climvstrstartdate1 = 0
583     climvstrstartdate2 = 0
584     climvstrperiod = 0
585     climvstrTauRelax = 0.0 _d 0
586     climvstrconst = 0.0 _d 0
587     climvstr_exfremo_intercept = 0.0 _d 0
588     climvstr_exfremo_slope = 0.0 _d 0
589    
590     useOBCSYearlyFields = .FALSE.
591     obcsNstartdate1 = 0
592     obcsNstartdate2 = 0
593     obcsNperiod = 0.0 _d 0
594     obcsSstartdate1 = 0
595     obcsSstartdate2 = 0
596     obcsSperiod = 0.0 _d 0
597     obcsEstartdate1 = 0
598     obcsEstartdate2 = 0
599     obcsEperiod = 0.0 _d 0
600     obcsWstartdate1 = 0
601     obcsWstartdate2 = 0
602     obcsWperiod = 0.0 _d 0
603    
604     siobNstartdate1 = UNSET_I
605     siobNstartdate2 = UNSET_I
606     siobNperiod = UNSET_RL
607     siobSstartdate1 = UNSET_I
608     siobSstartdate2 = UNSET_I
609     siobSperiod = UNSET_RL
610     siobEstartdate1 = UNSET_I
611     siobEstartdate2 = UNSET_I
612     siobEperiod = UNSET_RL
613     siobWstartdate1 = UNSET_I
614     siobWstartdate2 = UNSET_I
615     siobWperiod = UNSET_RL
616    
617     repeatPeriod = 0.0 _d 0
618     windstressmax = 2.0 _d 0
619    
620     exf_scal_BulkCdn = 1.0 _d 0
621    
622     C Initialise freezing temperature of sea water
623     climtempfreeze = -1.9 _d 0
624    
625     C Data files.
626     hfluxfile = ' '
627     atempfile = ' '
628     aqhfile = ' '
629     hs_file = ' '
630     hl_file = ' '
631     evapfile = ' '
632     precipfile = ' '
633     snowprecipfile = ' '
634     sfluxfile = ' '
635     runofffile = ' '
636     runoftempfile = ' '
637     saltflxfile = ' '
638     ustressfile = ' '
639     vstressfile = ' '
640     uwindfile = ' '
641     vwindfile = ' '
642     wspeedfile = ' '
643     swfluxfile = ' '
644     lwfluxfile = ' '
645     swdownfile = ' '
646     lwdownfile = ' '
647     apressurefile = ' '
648     tidePotFile = ' '
649     areamaskfile = ' '
650     climsstfile = ' '
651     climsssfile = ' '
652     climustrfile = ' '
653     climvstrfile = ' '
654     apco2file = ' '
655    
656     C Start Time.
657     hfluxStartTime = UNSET_RL
658     atempStartTime = UNSET_RL
659     aqhStartTime = UNSET_RL
660     hs_StartTime = UNSET_RL
661     hl_StartTime = UNSET_RL
662     evapStartTime = UNSET_RL
663     precipStartTime = UNSET_RL
664     snowprecipStartTime= UNSET_RL
665     sfluxStartTime = UNSET_RL
666     runoffStartTime = UNSET_RL
667     saltflxStartTime = UNSET_RL
668     ustressStartTime = UNSET_RL
669     vstressStartTime = UNSET_RL
670     uwindStartTime = UNSET_RL
671     vwindStartTime = UNSET_RL
672     wspeedStartTime = UNSET_RL
673     swfluxStartTime = UNSET_RL
674     lwfluxStartTime = UNSET_RL
675     swdownStartTime = UNSET_RL
676     lwdownStartTime = UNSET_RL
677     apressureStartTime = UNSET_RL
678     tidePotStartTime = UNSET_RL
679     areamaskStartTime = UNSET_RL
680     climsstStartTime = UNSET_RL
681     climsssStartTime = UNSET_RL
682     climustrStartTime = UNSET_RL
683     climvstrStartTime = UNSET_RL
684     obcsNstartTime = UNSET_RL
685     obcsSstartTime = UNSET_RL
686     obcsEstartTime = UNSET_RL
687     obcsWstartTime = UNSET_RL
688     siobNstartTime = UNSET_RL
689     siobSstartTime = UNSET_RL
690     siobEstartTime = UNSET_RL
691     siobWstartTime = UNSET_RL
692     apco2StartTime = UNSET_RL
693    
694     C Initialise file type and field precision
695     exf_iprec = 32
696     exf_iprec_obcs = UNSET_I
697     exf_yftype = 'RL'
698     useExfYearlyFields = .FALSE.
699     twoDigitYear = .FALSE.
700    
701     C Input scaling factors.
702     exf_inscal_hflux = 1. _d 0
703     exf_inscal_sflux = 1. _d 0
704     exf_inscal_ustress = 1. _d 0
705     exf_inscal_vstress = 1. _d 0
706     exf_inscal_uwind = 1. _d 0
707     exf_inscal_vwind = 1. _d 0
708     exf_inscal_wspeed = 1. _d 0
709     exf_inscal_swflux = 1. _d 0
710     exf_inscal_lwflux = 1. _d 0
711     exf_inscal_precip = 1. _d 0
712     exf_inscal_snowprecip= 1. _d 0
713     c exf_inscal_sst = 1. _d 0
714     c exf_inscal_sss = 1. _d 0
715     exf_inscal_atemp = 1. _d 0
716     exf_offset_atemp = 0. _d 0
717     exf_inscal_aqh = 1. _d 0
718     exf_inscal_hs = 1. _d 0
719     exf_inscal_hl = 1. _d 0
720     exf_inscal_evap = 1. _d 0
721     exf_inscal_apressure = 1. _d 0
722     exf_inscal_runoff = 1. _d 0
723     exf_inscal_runoftemp = 1. _d 0
724     exf_inscal_saltflx = 1. _d 0
725     exf_inscal_swdown = 1. _d 0
726     exf_inscal_lwdown = 1. _d 0
727     exf_inscal_climsst = 1. _d 0
728     exf_inscal_climsss = 1. _d 0
729     exf_inscal_climustr = 1. _d 0
730     exf_inscal_climvstr = 1. _d 0
731     exf_inscal_tidePot = 1. _d 0
732     exf_inscal_areamask = 1. _d 0
733     exf_inscal_apco2 = 1. _d 0
734    
735     C Output scaling factors.
736     exf_outscal_hflux = 1. _d 0
737     exf_outscal_sflux = 1. _d 0
738     exf_outscal_ustress = 1. _d 0
739     exf_outscal_vstress = 1. _d 0
740     exf_outscal_swflux = 1. _d 0
741     exf_outscal_sst = 1. _d 0
742     exf_outscal_sss = 1. _d 0
743     exf_outscal_apressure= 1. _d 0
744     exf_outscal_tidePot = 1. _d 0
745     exf_outscal_areamask = 1. _d 0
746     exf_outscal_apco2 = 1. _d 0
747    
748     #ifdef USE_EXF_INTERPOLATION
749     C-- set default input location to match (in case of simple Lat-Lonp grid)
750     C model grid cell-center position (leading to trivial interpolation)
751     inp_lon0 = xgOrigin + delX(1)*exf_half
752     inp_lat0 = ygOrigin + delY(1)*exf_half
753     inp_dLon = delX(1)
754     inp_dLat = delY(1)
755    
756     ustress_lon0 = inp_lon0
757     uwind_lon0 = inp_lon0
758     vstress_lon0 = inp_lon0
759     hflux_lon0 = inp_lon0
760     sflux_lon0 = inp_lon0
761     swflux_lon0 = inp_lon0
762     runoff_lon0 = inp_lon0
763     saltflx_lon0 = inp_lon0
764     atemp_lon0 = inp_lon0
765     aqh_lon0 = inp_lon0
766     hs_lon0 = inp_lon0
767     hl_lon0 = inp_lon0
768     evap_lon0 = inp_lon0
769     precip_lon0 = inp_lon0
770     snowprecip_lon0= inp_lon0
771     vwind_lon0 = inp_lon0
772     wspeed_lon0 = inp_lon0
773     lwflux_lon0 = inp_lon0
774     swdown_lon0 = inp_lon0
775     lwdown_lon0 = inp_lon0
776     apressure_lon0 = inp_lon0
777     tidePot_lon0 = inp_lon0
778     areamask_lon0 = inp_lon0
779     vstress_lat0 = inp_lat0
780     vwind_lat0 = inp_lat0
781     wspeed_lat0 = inp_lat0
782     ustress_lat0 = inp_lat0
783     hflux_lat0 = inp_lat0
784     sflux_lat0 = inp_lat0
785     runoff_lat0 = inp_lat0
786     saltflx_lat0 = inp_lat0
787     swflux_lat0 = inp_lat0
788     atemp_lat0 = inp_lat0
789     aqh_lat0 = inp_lat0
790     hs_lat0 = inp_lat0
791     hl_lat0 = inp_lat0
792     evap_lat0 = inp_lat0
793     precip_lat0 = inp_lat0
794     snowprecip_lat0= inp_lat0
795     uwind_lat0 = inp_lat0
796     lwflux_lat0 = inp_lat0
797     swdown_lat0 = inp_lat0
798     lwdown_lat0 = inp_lat0
799     apressure_lat0 = inp_lat0
800     tidePot_lat0 = inp_lat0
801     areamask_lat0 = inp_lat0
802     ustress_nlon = gridNx
803     ustress_nlat = gridNy
804     vstress_nlon = gridNx
805     vstress_nlat = gridNy
806     hflux_nlon = gridNx
807     hflux_nlat = gridNy
808     sflux_nlon = gridNx
809     sflux_nlat = gridNy
810     swflux_nlon = gridNx
811     swflux_nlat = gridNy
812     runoff_nlon = gridNx
813     runoff_nlat = gridNy
814     saltflx_nlon = gridNx
815     saltflx_nlat = gridNy
816     atemp_nlon = gridNx
817     atemp_nlat = gridNy
818     aqh_nlon = gridNx
819     aqh_nlat = gridNy
820     hs_nlon = gridNx
821     hs_nlat = gridNy
822     hl_nlon = gridNx
823     hl_nlat = gridNy
824     evap_nlon = gridNx
825     evap_nlat = gridNy
826     precip_nlon = gridNx
827     precip_nlat = gridNy
828     snowprecip_nlon= gridNx
829     snowprecip_nlat= gridNy
830     uwind_nlon = gridNx
831     uwind_nlat = gridNy
832     vwind_nlon = gridNx
833     vwind_nlat = gridNy
834     wspeed_nlon = gridNx
835     wspeed_nlat = gridNy
836     lwflux_nlon = gridNx
837     lwflux_nlat = gridNy
838     swdown_nlon = gridNx
839     swdown_nlat = gridNy
840     lwdown_nlon = gridNx
841     lwdown_nlat = gridNy
842     apressure_nlon = gridNx
843     apressure_nlat = gridNy
844     tidePot_nlon = gridNx
845     tidePot_nlat = gridNy
846     areamask_nlon = gridNx
847     areamask_nlat = gridNy
848     ustress_lon_inc = inp_dLon
849     vstress_lon_inc = inp_dLon
850     hflux_lon_inc = inp_dLon
851     sflux_lon_inc = inp_dLon
852     swflux_lon_inc = inp_dLon
853     runoff_lon_inc = inp_dLon
854     saltflx_lon_inc = inp_dLon
855     atemp_lon_inc = inp_dLon
856     aqh_lon_inc = inp_dLon
857     hs_lon_inc = inp_dLon
858     hl_lon_inc = inp_dLon
859     evap_lon_inc = inp_dLon
860     precip_lon_inc = inp_dLon
861     snowprecip_lon_inc= inp_dLon
862     uwind_lon_inc = inp_dLon
863     vwind_lon_inc = inp_dLon
864     wspeed_lon_inc = inp_dLon
865     lwflux_lon_inc = inp_dLon
866     swdown_lon_inc = inp_dLon
867     lwdown_lon_inc = inp_dLon
868     apressure_lon_inc = inp_dLon
869     tidePot_lon_inc = inp_dLon
870     areamask_lon_inc = inp_dLon
871    
872     climsst_lon0 = inp_lon0
873     climsss_lon0 = inp_lon0
874     climustr_lon0 = inp_lon0
875     climvstr_lon0 = inp_lon0
876     climsst_lat0 = inp_lat0
877     climsss_lat0 = inp_lat0
878     climustr_lat0 = inp_lat0
879     climvstr_lat0 = inp_lat0
880     climsst_nlon = gridNx
881     climsst_nlat = gridNy
882     climsss_nlon = gridNx
883     climsss_nlat = gridNy
884     climustr_nlon = gridNx
885     climustr_nlat = gridNy
886     climvstr_nlon = gridNx
887     climvstr_nlat = gridNy
888     climsst_lon_inc = inp_dLon
889     climsss_lon_inc = inp_dLon
890     climustr_lon_inc= inp_dLon
891     climvstr_lon_inc= inp_dLon
892     apco2_lon0 = inp_lon0
893     apco2_lat0 = inp_lat0
894     apco2_nlon = gridNx
895     apco2_nlat = gridNy
896     apco2_lon_inc = inp_dLon
897    
898     DO j=1,MAX_LAT_INC
899     IF (j.LT.gridNy) THEN
900     inp_dLat = (delY(j) + delY(j+1))*exf_half
901     ELSE
902     inp_dLat = 0.
903     ENDIF
904     ustress_lat_inc(j) = inp_dLat
905     vstress_lat_inc(j) = inp_dLat
906     hflux_lat_inc(j) = inp_dLat
907     sflux_lat_inc(j) = inp_dLat
908     swflux_lat_inc(j) = inp_dLat
909     runoff_lat_inc(j) = inp_dLat
910     saltflx_lat_inc(j) = inp_dLat
911     atemp_lat_inc(j) = inp_dLat
912     aqh_lat_inc(j) = inp_dLat
913     hs_lat_inc(j) = inp_dLat
914     hl_lat_inc(j) = inp_dLat
915     evap_lat_inc(j) = inp_dLat
916     precip_lat_inc(j) = inp_dLat
917     snowprecip_lat_inc(j)= inp_dLat
918     uwind_lat_inc(j) = inp_dLat
919     vwind_lat_inc(j) = inp_dLat
920     wspeed_lat_inc(j) = inp_dLat
921     lwflux_lat_inc(j) = inp_dLat
922     swdown_lat_inc(j) = inp_dLat
923     lwdown_lat_inc(j) = inp_dLat
924     apressure_lat_inc(j) = inp_dLat
925     tidePot_lat_inc(j) = inp_dLat
926     areamask_lat_inc(j) = inp_dLat
927     climsst_lat_inc(j) = inp_dLat
928     climsss_lat_inc(j) = inp_dLat
929     climustr_lat_inc(j) = inp_dLat
930     climvstr_lat_inc(j) = inp_dLat
931     apco2_lat_inc(j) = inp_dLat
932     ENDDO
933    
934     ustress_interpMethod = 12
935     vstress_interpMethod = 22
936     hflux_interpMethod = 1
937     sflux_interpMethod = 1
938     swflux_interpMethod = 1
939     runoff_interpMethod = 1
940     saltflx_interpMethod = 1
941     atemp_interpMethod = 1
942     aqh_interpMethod = 1
943     hs_interpMethod = 1
944     hl_interpMethod = 1
945     evap_interpMethod = 1
946     precip_interpMethod = 1
947     snowprecip_interpMethod= 1
948     uwind_interpMethod = 12
949     vwind_interpMethod = 22
950     wspeed_interpMethod = 1
951     lwflux_interpMethod = 1
952     swdown_interpMethod = 1
953     lwdown_interpMethod = 1
954     apressure_interpMethod = 1
955     tidePot_interpMethod = 1
956     areamask_interpMethod = 1
957     climsst_interpMethod = 2
958     climsss_interpMethod = 2
959     climustr_interpMethod = 12
960     climvstr_interpMethod = 22
961     apco2_interpMethod = 1
962    
963     exf_output_interp = .FALSE.
964     #endif /* USE_EXF_INTERPOLATION */
965    
966     C-- Next, read pkg/exf parameter file.
967     WRITE(msgBuf,'(A)') 'EXF_READPARMS: opening data.exf'
968     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
969     & SQUEEZE_RIGHT, myThid )
970    
971     CALL OPEN_COPY_DATA_FILE(
972     I 'data.exf', 'EXF_READPARMS',
973     O iUnit,
974     I myThid )
975    
976     WRITE(msgBuf,'(A)')
977     & 'EXF_READPARMS: reading EXF_NML_01'
978     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
979     & SQUEEZE_RIGHT, myThid )
980     READ( iUnit, nml = EXF_NML_01 )
981     C- Set default fldRepeatCycle to repeatPeriod
982     hfluxRepCycle = repeatPeriod
983     atempRepCycle = repeatPeriod
984     aqhRepCycle = repeatPeriod
985     hs_RepCycle = repeatPeriod
986     hl_RepCycle = repeatPeriod
987     evapRepCycle = repeatPeriod
988     precipRepCycle = repeatPeriod
989     snowprecipRepCycle = repeatPeriod
990     sfluxRepCycle = repeatPeriod
991     runoffRepCycle = repeatPeriod
992     saltflxRepCycle = repeatPeriod
993     ustressRepCycle = repeatPeriod
994     vstressRepCycle = repeatPeriod
995     uwindRepCycle = repeatPeriod
996     vwindRepCycle = repeatPeriod
997     wspeedRepCycle = repeatPeriod
998     swfluxRepCycle = repeatPeriod
999     lwfluxRepCycle = repeatPeriod
1000     swdownRepCycle = repeatPeriod
1001     lwdownRepCycle = repeatPeriod
1002     apressureRepCycle = repeatPeriod
1003     tidePotRepCycle = repeatPeriod
1004     areamaskRepCycle = repeatPeriod
1005     climsstRepCycle = repeatPeriod
1006     climsssRepCycle = repeatPeriod
1007     climustrRepCycle = repeatPeriod
1008     climvstrRepCycle = repeatPeriod
1009     apco2RepCycle = repeatPeriod
1010    
1011     C-
1012     obcsNrepCycle = repeatPeriod
1013     obcsSrepCycle = repeatPeriod
1014     obcsErepCycle = repeatPeriod
1015     obcsWrepCycle = repeatPeriod
1016     siobNrepCycle = UNSET_RL
1017     siobSrepCycle = UNSET_RL
1018     siobErepCycle = UNSET_RL
1019     siobWrepCycle = UNSET_RL
1020    
1021     WRITE(msgBuf,'(A)')
1022     & 'EXF_READPARMS: reading EXF_NML_02'
1023     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1024     & SQUEEZE_RIGHT, myThid )
1025     READ( iUnit, nml = EXF_NML_02 )
1026     WRITE(msgBuf,'(A)')
1027     & 'EXF_READPARMS: reading EXF_NML_03'
1028     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1029     & SQUEEZE_RIGHT, myThid )
1030     READ( iUnit, nml = EXF_NML_03 )
1031     #ifdef USE_EXF_INTERPOLATION
1032     WRITE(msgBuf,'(A)')
1033     & 'EXF_READPARMS: reading EXF_NML_04'
1034     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1035     & SQUEEZE_RIGHT, myThid )
1036     READ( iUnit, nml = EXF_NML_04 )
1037     #endif /* USE_EXF_INTERPOLATION */
1038    
1039     #ifdef ALLOW_OBCS
1040     IF ( useOBCS ) THEN
1041     WRITE(msgBuf,'(A)')
1042     & 'EXF_READPARMS: reading EXF_NML_OBCS'
1043     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1044     & SQUEEZE_RIGHT, myThid )
1045     READ( iUnit, nml = EXF_NML_OBCS )
1046     ENDIF
1047     IF(siobNstartdate1.EQ.UNSET_I ) siobNstartdate1=obcsNstartdate1
1048     IF(siobNstartdate2.EQ.UNSET_I ) siobNstartdate2=obcsNstartdate2
1049     IF(siobNperiod .EQ.UNSET_RL) siobNperiod =obcsNperiod
1050     IF(siobNrepCycle .EQ.UNSET_RL) siobNrepCycle =obcsNrepCycle
1051     IF(siobSstartdate1.EQ.UNSET_I ) siobSstartdate1=obcsSstartdate1
1052     IF(siobSstartdate2.EQ.UNSET_I ) siobSstartdate2=obcsSstartdate2
1053     IF(siobSperiod .EQ.UNSET_RL) siobSperiod =obcsSperiod
1054     IF(siobSrepCycle .EQ.UNSET_RL) siobSrepCycle =obcsSrepCycle
1055     IF(siobEstartdate1.EQ.UNSET_I ) siobEstartdate1=obcsEstartdate1
1056     IF(siobEstartdate2.EQ.UNSET_I ) siobEstartdate2=obcsEstartdate2
1057     IF(siobEperiod .EQ.UNSET_RL) siobEperiod =obcsEperiod
1058     IF(siobErepCycle .EQ.UNSET_RL) siobErepCycle =obcsErepCycle
1059     IF(siobWstartdate1.EQ.UNSET_I ) siobWstartdate1=obcsWstartdate1
1060     IF(siobWstartdate2.EQ.UNSET_I ) siobWstartdate2=obcsWstartdate2
1061     IF(siobWperiod .EQ.UNSET_RL) siobWperiod =obcsWperiod
1062     IF(siobWrepCycle .EQ.UNSET_RL) siobWrepCycle =obcsWrepCycle
1063    
1064     IF(exf_iprec_obcs .EQ. UNSET_I) exf_iprec_obcs =exf_iprec
1065     #endif /* ALLOW_OBCS */
1066    
1067     WRITE(msgBuf,'(A)')
1068     & 'EXF_READPARMS: finished reading data.exf'
1069     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1070     & SQUEEZE_RIGHT, myThid )
1071    
1072     #ifdef SINGLE_DISK_IO
1073     CLOSE(iUnit)
1074     #else
1075     CLOSE(iUnit,STATUS='DELETE')
1076     #endif /* SINGLE_DISK_IO */
1077    
1078     C-- Retired parameters
1079     IF ( exf_yftype.NE.'RL' ) THEN
1080     STOP 'S/R EXF_READPARAMS: value of exf_yftype not allowed'
1081     ENDIF
1082    
1083     C-- Derive other parameters:
1084     IF ( exf_verbose ) exf_debugLev = MAX( exf_debugLev, debLevD )
1085     hq = ht
1086     stressIsOnCgrid = readStressOnCgrid
1087     #if ( defined (ALLOW_BULKFORMULAE) )
1088     IF ( useAtmWind ) stressIsOnCgrid = .FALSE.
1089     #endif
1090     #ifdef USE_EXF_INTERPOLATION
1091     IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
1092     & (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') )
1093     & stressIsOnCgrid = .FALSE.
1094     #endif /* USE_EXF_INTERPOLATION */
1095    
1096     useExfZenAlbedo = select_ZenAlbedo.GE.1
1097     & .AND. select_ZenAlbedo.LE.3
1098    
1099     C-- Overwrite tauThetaClimRelax but stop if already set.
1100     C- Note: need this, even if EXF option ALLOW_CLIMSST_RELAXATION is undef;
1101     C this prevents to apply relaxation towards potentially wrong SST since,
1102     C with EXF, we skip the update of loaded SST in EXTERNAL_FIELDS_LOAD.
1103     C- Note2: let s see whether we can put this back under ifdef
1104     C ALLOW_CLIMSST_RELAXATION, but always call EXTERNAL_FIELDS_LOAD.
1105     C If ALLOW_CLIMSST_RELAXATION is undef, clim.relaxation could still
1106     C be done outside of exf.
1107     #ifdef ALLOW_CLIMSST_RELAXATION
1108     IF ( tauThetaClimRelax.NE.0. _d 0 ) THEN
1109     WRITE(msgBuf,'(2A)') 'EXF_READPARMS: ',
1110     & 'with EXF, cannot use "tauThetaClimRelax" in "data"'
1111     CALL PRINT_ERROR( msgBuf, myThid )
1112     WRITE(msgBuf,'(2A)') 'since SST relax. is handled by EXF',
1113     & ' (data.exf, "climsstTauRelax")'
1114     CALL PRINT_ERROR( msgBuf, myThid )
1115     STOP 'ABNORMAL END: S/R EXF_READPARMS'
1116     ENDIF
1117     tauThetaClimRelax = climsstTauRelax
1118     #endif
1119    
1120     #ifdef ALLOW_CLIMSSS_RELAXATION
1121     C-- Overwrite tauSaltClimRelax but stop if already set.
1122     IF ( tauSaltClimRelax.NE.0. _d 0 ) THEN
1123     WRITE(msgBuf,'(2A)') 'EXF_READPARMS: ',
1124     & 'with EXF, cannot use "tauSaltClimRelax" in "data"'
1125     CALL PRINT_ERROR( msgBuf, myThid )
1126     WRITE(msgBuf,'(2A)') 'since SSS relax. is handled by EXF',
1127     & ' (data.exf, "climsssTauRelax")'
1128     CALL PRINT_ERROR( msgBuf, myThid )
1129     STOP 'ABNORMAL END: S/R EXF_READPARMS'
1130     ENDIF
1131     tauSaltClimRelax = climsssTauRelax
1132     #endif
1133    
1134     C Complete the start date specifications for the forcing
1135     C fields to get a complete calendar date array.
1136     C => moved to EXF_INIT_FIXED
1137    
1138     _END_MASTER( myThid )
1139     _BARRIER
1140    
1141     RETURN
1142     END

  ViewVC Help
Powered by ViewVC 1.1.22