/[MITgcm]/MITgcm/pkg/exf/exf_readparms.F
ViewVC logotype

Diff of /MITgcm/pkg/exf/exf_readparms.F

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

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

Legend:
Removed from v.1.4.2.1  
changed lines
  Added in v.1.94

  ViewVC Help
Powered by ViewVC 1.1.22