/[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.77 by jmc, Sat Nov 10 21:57:39 2012 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    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          CHARACTER*(2) exf_yftype
74          CHARACTER*(MAX_LEN_MBUF) msgBuf
75    C     == end of interface ==
76    
77    C     Surface flux data.
78          NAMELIST /EXF_NML_01/
79         &      windstressmax,       repeatPeriod,    exf_albedo,
80         &   ocean_emissivity,     ice_emissivity, snow_emissivity,
81         &          exf_iceCd,          exf_iceCe,     exf_iceCh,
82         &   exf_scal_BulkCdn,     climtempfreeze,
83         &          exf_iprec,     exf_iprec_obcs,     exf_yftype,
84         &        exf_verbose,   useExfCheckRange,     exf_monFreq,
85         & useExfYearlyFields,  twoDigitYear,
86         & useStabilityFct_overIce, readStressOnAgrid, readStressOnCgrid,
87         & useAtmWind, useRelativeWind, noNegativeEvap,
88         & select_ZenAlbedo, useExfZenIncoming,
89         & hu, ht, umin, atmrho, atmcp, cen2kel, gravity_mks,
90         & cdrag_1, cdrag_2, cdrag_3, cstanton_1, cstanton_2, cdalton,
91         & flamb, flami, zolmin, zref,
92         & cvapor_fac, cvapor_exp, cvapor_fac_ice, cvapor_exp_ice,
93         & humid_fac, gamma_blk, saltsat, sstExtrapol, psim_fac
94    
95        integer  ilnblnk        NAMELIST /EXF_NML_02/
96        external ilnblnk       &          hfluxfile,          atempfile,       aqhfile,
97         &          sfluxfile,         precipfile,    runofffile,
98  c     == end of interface ==       &        ustressfile,        vstressfile,      evapfile,
99         &     snowprecipfile,          uwindfile,     vwindfile,
100  c     Surface flux data.       &         wspeedfile,         swfluxfile,    lwfluxfile,
101        namelist /exf_nml/       &      apressurefile,         swdownfile,    lwdownfile,
102       &    repeatPeriod,       &       areamaskfile,        climsstfile,   climsssfile,
103         &                           climustrfile,  climvstrfile,
104       &    hfluxstartdate1,    hfluxstartdate2,   hfluxperiod,       &    hfluxstartdate1,    hfluxstartdate2,   hfluxperiod,
105       &    atempstartdate1,    atempstartdate2,   atempperiod,       &    atempstartdate1,    atempstartdate2,   atempperiod,
106       &      aqhstartdate1,      aqhstartdate2,     aqhperiod,       &      aqhstartdate1,      aqhstartdate2,     aqhperiod,
107       &    sfluxstartdate1,    sfluxstartdate2,   sfluxperiod,       &    sfluxstartdate1,    sfluxstartdate2,   sfluxperiod,
108         &     evapstartdate1,     evapstartdate2,    evapperiod,
109       &   precipstartdate1,   precipstartdate2,  precipperiod,       &   precipstartdate1,   precipstartdate2,  precipperiod,
110         & snowprecipstartdate1, snowprecipstartdate2, snowprecipperiod,
111       &   runoffstartdate1,   runoffstartdate2,  runoffperiod,       &   runoffstartdate1,   runoffstartdate2,  runoffperiod,
112       &  ustressstartdate1,  ustressstartdate2, ustressperiod,       &  ustressstartdate1,  ustressstartdate2, ustressperiod,
113       &  vstressstartdate1,  vstressstartdate2, vstressperiod,       &  vstressstartdate1,  vstressstartdate2, vstressperiod,
114       &    uwindstartdate1,    uwindstartdate2,   uwindperiod,       &    uwindstartdate1,    uwindstartdate2,   uwindperiod,
115       &    vwindstartdate1,    vwindstartdate2,   vwindperiod,       &    vwindstartdate1,    vwindstartdate2,   vwindperiod,
116         &   wspeedstartdate1,   wspeedstartdate2,  wspeedperiod,
117       &   swfluxstartdate1,   swfluxstartdate2,  swfluxperiod,       &   swfluxstartdate1,   swfluxstartdate2,  swfluxperiod,
118       &   lwfluxstartdate1,   lwfluxstartdate2,  lwfluxperiod,       &   lwfluxstartdate1,   lwfluxstartdate2,  lwfluxperiod,
119         &   swdownstartdate1,   swdownstartdate2,  swdownperiod,
120         &   lwdownstartdate1,   lwdownstartdate2,  lwdownperiod,
121         &apressurestartdate1,apressurestartdate2,apressureperiod,
122         &  areamaskstartdate1,areamaskstartdate2,areamaskperiod,
123         &  climsststartdate1,  climsststartdate2, climsstperiod,
124         &  climsssstartdate1,  climsssstartdate2, climsssperiod,
125         & climustrstartdate1, climustrstartdate2,climustrperiod,
126         & climvstrstartdate1, climvstrstartdate2,climvstrperiod,
127         &   areamaskTauRelax,    climsstTauRelax, climsssTauRelax,
128         &   climustrTauRelax,climvstrTauRelax
129    
130          NAMELIST /EXF_NML_03/
131         &   exf_inscal_hflux,  exf_inscal_sflux,      exf_inscal_evap,
132         & exf_inscal_ustress,  exf_inscal_vstress,
133         &   exf_inscal_uwind,  exf_inscal_vwind,    exf_inscal_wspeed,
134         &   exf_inscal_atemp,  exf_offset_atemp,       exf_inscal_aqh,
135         &     exf_inscal_sst,  exf_inscal_sss,
136         &  exf_inscal_swflux,  exf_inscal_lwflux,   exf_inscal_precip,
137         &  exf_inscal_runoff,  exf_inscal_apressure, exf_inscal_snowprecip,
138         &  exf_inscal_swdown,  exf_inscal_lwdown,
139         & exf_inscal_climsst, exf_inscal_climsss,
140         & exf_inscal_climustr, exf_inscal_climvstr,
141         &  exf_outscal_hflux,  exf_outscal_ustress, exf_outscal_vstress,
142         & exf_outscal_swflux,  exf_outscal_sst,     exf_outscal_sss,
143         &  exf_outscal_sflux,  exf_outscal_apressure,
144         & exf_inscal_areamask, exf_outscal_areamask,
145         &  hfluxconst, atempconst, aqhconst, sfluxconst, evapconst,
146         &  precipconst, snowprecipconst, runoffconst, ustressconst,
147         &  vstressconst, uwindconst, vwindconst, wspeedconst, swfluxconst,
148         &  lwfluxconst, swdownconst, lwdownconst, apressureconst,
149         &  areamaskconst, climsstconst,   climsssconst,
150         &  climustrconst, climvstrconst,
151         &     hflux_exfremo_intercept, hflux_exfremo_slope,
152         &     atemp_exfremo_intercept, atemp_exfremo_slope,
153         &     aqh_exfremo_intercept, aqh_exfremo_slope,
154         &     sflux_exfremo_intercept, sflux_exfremo_slope,
155         &     evap_exfremo_intercept, evap_exfremo_slope,
156         &     precip_exfremo_intercept, precip_exfremo_slope,
157         &     snowprecip_exfremo_intercept, snowprecip_exfremo_slope,
158         &     runoff_exfremo_intercept, runoff_exfremo_slope,
159         &     ustress_exfremo_intercept, ustress_exfremo_slope,
160         &     vstress_exfremo_intercept, vstress_exfremo_slope,
161         &     uwind_exfremo_intercept, uwind_exfremo_slope,
162         &     vwind_exfremo_intercept, vwind_exfremo_slope,
163         &     wspeed_exfremo_intercept, wspeed_exfremo_slope,
164         &     swflux_exfremo_intercept, swflux_exfremo_slope,
165         &     lwflux_exfremo_intercept, lwflux_exfremo_slope,
166         &     swdown_exfremo_intercept, swdown_exfremo_slope,
167         &     lwdown_exfremo_intercept, lwdown_exfremo_slope,
168         &     apressure_exfremo_intercept, apressure_exfremo_slope,
169         &     areamask_exfremo_intercept, areamask_exfremo_slope,
170         &     climsst_exfremo_intercept, climsst_exfremo_slope,
171         &     climsss_exfremo_intercept, climsss_exfremo_slope,
172         &     climustr_exfremo_intercept, climustr_exfremo_slope,
173         &     climvstr_exfremo_intercept, climvstr_exfremo_slope
174    
175    #ifdef USE_EXF_INTERPOLATION
176          NAMELIST /EXF_NML_04/
177         & ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
178         & ustress_nlon, ustress_nlat, ustress_interpMethod,
179         & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
180         & vstress_nlon, vstress_nlat, vstress_interpMethod,
181         & hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
182         & hflux_nlon, hflux_nlat, hflux_interpMethod,
183         & sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
184         & sflux_nlon, sflux_nlat, sflux_interpMethod,
185         & swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
186         & swflux_nlon, swflux_nlat, swflux_interpMethod,
187         & lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
188         & lwflux_nlon, lwflux_nlat, lwflux_interpMethod,
189         & atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
190         & atemp_nlon, atemp_nlat, atemp_interpMethod,
191         & aqh_lon0, aqh_lon_inc, aqh_lat0,aqh_lat_inc,
192         & aqh_nlon, aqh_nlat, aqh_interpMethod,
193         & evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
194         & evap_nlon, evap_nlat, evap_interpMethod,
195         & precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
196         & precip_nlon, precip_nlat, precip_interpMethod,
197         & runoff_lon0, runoff_lon_inc, runoff_lat0, runoff_lat_inc,
198         & runoff_nlon, runoff_nlat, runoff_interpMethod,
199         & snowprecip_lon0, snowprecip_lon_inc,
200         & snowprecip_lat0, snowprecip_lat_inc,
201         & snowprecip_nlon, snowprecip_nlat, snowprecip_interpMethod,
202         & uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
203         & uwind_nlon, uwind_nlat, uwind_interpMethod,
204         & vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
205         & vwind_nlon, vwind_nlat, vwind_interpMethod,
206         & wspeed_lon0, wspeed_lon_inc, wspeed_lat0, wspeed_lat_inc,
207         & wspeed_nlon, wspeed_nlat, wspeed_interpMethod,
208         & swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
209         & swdown_nlon, swdown_nlat, swdown_interpMethod,
210         & lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
211         & lwdown_nlon, lwdown_nlat, lwdown_interpMethod,
212         & apressure_lon0,apressure_lon_inc,apressure_lat0,apressure_lat_inc
213         & , apressure_nlon, apressure_nlat, apressure_interpMethod,
214         & areamask_lon0, areamask_lon_inc, areamask_lat0, areamask_lat_inc,
215         & areamask_nlon, areamask_nlat, areamask_interpMethod,
216         & climsst_lon0, climsst_lon_inc, climsst_lat0, climsst_lat_inc,
217         & climsst_nlon, climsst_nlat, climsst_interpMethod,
218         & climsss_lon0, climsss_lon_inc,climsss_lat0, climsss_lat_inc,
219         & climsss_nlon, climsss_nlat, climsss_interpMethod,
220         & climustr_lon0, climustr_lon_inc, climustr_lat0, climustr_lat_inc,
221         & climustr_nlon, climustr_nlat, climustr_interpMethod,
222         & climvstr_lon0, climvstr_lon_inc, climvstr_lat0, climvstr_lat_inc,
223         & climvstr_nlon, climvstr_nlat, climvstr_interpMethod
224    #endif /* USE_EXF_INTERPOLATION */
225    
226    #ifdef ALLOW_ICEFRONT
227          NAMELIST /EXF_NML_SGRUNOFF/
228         &    sgrunoffstartdate1, sgrunoffstartdate2,
229         &    sgrunoffstartdate,  sgrunoffperiod,
230         &    sgrunoffconst,      sgrunoff_exfremo_intercept,
231         &    sgrunoff_exfremo_slope, exf_inscal_sgrunoff
232    #endif /* ALLOW_ICEFRONT */
233    
234    #ifdef ALLOW_OBCS
235          NAMELIST /EXF_NML_OBCS/
236         &    useOBCSYearlyFields,
237       &    obcsNstartdate1,    obcsNstartdate2,   obcsNperiod,       &    obcsNstartdate1,    obcsNstartdate2,   obcsNperiod,
238       &    obcsSstartdate1,    obcsSstartdate2,   obcsSperiod,       &    obcsSstartdate1,    obcsSstartdate2,   obcsSperiod,
239       &    obcsEstartdate1,    obcsEstartdate2,   obcsEperiod,       &    obcsEstartdate1,    obcsEstartdate2,   obcsEperiod,
240       &    obcsWstartdate1,    obcsWstartdate2,   obcsWperiod,       &    obcsWstartdate1,    obcsWstartdate2,   obcsWperiod,
241       &apressurestartdate1,apressurestartdate2,apressureperiod,       &    siobNstartdate1,    siobNstartdate2,   siobNperiod,
242       &          hfluxfile,          atempfile,       aqhfile,       &    siobSstartdate1,    siobSstartdate2,   siobSperiod,
243       &          sfluxfile,         precipfile,    runofffile,       &    siobEstartdate1,    siobEstartdate2,   siobEperiod,
244       &        ustressfile,        vstressfile,       &    siobWstartdate1,    siobWstartdate2,   siobWperiod
245       &          uwindfile,          vwindfile,  #endif /* ALLOW_OBCS */
246       &         swfluxfile,         lwfluxfile, apressurefile,  
247       &          exf_iprec,         exf_yftype,  #ifdef USE_EXF_INTERPOLATION
248       &           scal_hfl,           scal_ust,       scal_vst,  # ifdef ALLOW_EXCH2
249       &           scal_swf,           scal_sst,       scal_sss,        gridNx = exch2_mydNx(1)
250       &     scal_apressure,           scal_prc,       scal_sfl,        gridNy = exch2_mydNy(1)
251       &    windspeedstartdate1,    windspeedstartdate2,    # else /* ALLOW_EXCH2 */
252       &    windspeedperiod, windspeedfile        gridNx = Nx
253        _BEGIN_MASTER(mythid)        gridNy = Ny
254    # endif /* ALLOW_EXCH2 */
255    #endif /* USE_EXF_INTERPOLATION */
256    
257          _BEGIN_MASTER(myThid)
258    
259    C     Set default values.
260    
261          year2sec           = 365.*86400.
262          exf_verbose        = debugMode
263          exf_monFreq        = monitorFreq
264          useExfCheckRange   = .TRUE.
265          useExfZenAlbedo    = .FALSE.
266          select_ZenAlbedo   = 0
267          useExfZenIncoming  = .FALSE.
268          readStressOnAgrid  = .FALSE.
269          readStressOnCgrid  = .FALSE.
270    #ifdef ALLOW_ATM_WIND
271          useAtmWind         = .TRUE.
272    #else
273          useAtmWind         = .FALSE.
274    #endif
275          useRelativeWind    = .FALSE.
276          noNegativeEvap     = .FALSE.
277    
278  c     Set default values.  C-  default value should be set to main model parameter:
279    c     cen2kel     =  celsius2K
280    c     gravity_mks = gravity
281    c     atmcp       =  atm_Cp
282    c     humid_fac   =  atm_Rq     <- default is zero !!!
283    
284          cen2kel        =      273.150  _d 0
285          gravity_mks    =        9.81   _d 0
286          atmrho         =        1.200  _d 0
287          atmcp          =     1005.000  _d 0
288          flamb          =  2500000.000  _d 0
289          flami          =   334000.000  _d 0
290          cvapor_fac     =   640380.000  _d 0
291          cvapor_exp     =     5107.400  _d 0
292          cvapor_fac_ice = 11637800.000  _d 0
293          cvapor_exp_ice =     5897.800  _d 0
294          humid_fac      =        0.606  _d 0
295          gamma_blk      =        0.010  _d 0
296          saltsat        =        0.980  _d 0
297          sstExtrapol    =        0.0    _d 0
298          cdrag_1        =        0.0027000 _d 0
299          cdrag_2        =        0.0001420 _d 0
300          cdrag_3        =        0.0000764 _d 0
301          cstanton_1     =        0.0327 _d 0
302          cstanton_2     =        0.0180 _d 0
303          cdalton        =        0.0346 _d 0
304          zolmin         =     -100.000  _d 0
305          psim_fac       =        5.000  _d 0
306          zref           =       10.000  _d 0
307          hu             =       10.000  _d 0
308          ht             =        2.000  _d 0
309          umin           =        0.5    _d 0
310          useStabilityFct_overIce = .FALSE.
311          exf_iceCd        = 1.63 _d -3
312          exf_iceCe        = 1.63 _d -3
313          exf_iceCh        = 1.63 _d -3
314          exf_albedo       = 0.1 _d 0
315    C--   this default is chosen to be backward compatible with
316    C--   an earlier setting of 5.5 = ocean_emissivity*stefanBoltzmann
317          ocean_emissivity = 5.50 _d -8 / 5.670 _d -8
318          ice_emissivity   = 0.95 _d 0
319          snow_emissivity  = 0.95 _d 0
320    
321  c     Calendar data.  C     Calendar data.
322        hfluxstartdate1    = 0        hfluxstartdate1    = 0
323        hfluxstartdate2    = 0        hfluxstartdate2    = 0
324        hfluxperiod        = 0.0 _d 0        hfluxperiod        = 0.0 _d 0
325          hfluxconst         = 0.0 _d 0
326          hflux_exfremo_intercept = 0.0 _d 0
327          hflux_exfremo_slope = 0.0 _d 0
328    
329        atempstartdate1    = 0        atempstartdate1    = 0
330        atempstartdate2    = 0        atempstartdate2    = 0
331        atempperiod        = 0.0 _d 0        atempperiod        = 0.0 _d 0
332          atempconst         = celsius2K
333          atemp_exfremo_intercept = 0.0 _d 0
334          atemp_exfremo_slope = 0.0 _d 0
335    
336        aqhstartdate1      = 0        aqhstartdate1      = 0
337        aqhstartdate2      = 0        aqhstartdate2      = 0
338        aqhperiod          = 0.0 _d 0        aqhperiod          = 0.0 _d 0
339          aqhconst           = 0.0 _d 0
340          aqh_exfremo_intercept = 0.0 _d 0
341          aqh_exfremo_slope = 0.0 _d 0
342    
343        sfluxstartdate1    = 0        sfluxstartdate1    = 0
344        sfluxstartdate2    = 0        sfluxstartdate2    = 0
345        sfluxperiod        = 0.0 _d 0        sfluxperiod        = 0.0 _d 0
346          sfluxconst         = 0.0 _d 0
347          sflux_exfremo_intercept = 0.0 _d 0
348          sflux_exfremo_slope = 0.0 _d 0
349    
350          evapstartdate1   = 0
351          evapstartdate2   = 0
352          evapperiod       = 0.0 _d 0
353          evapconst        = 0.0 _d 0
354          evap_exfremo_intercept = 0.0 _d 0
355          evap_exfremo_slope = 0.0 _d 0
356    
357        precipstartdate1   = 0        precipstartdate1   = 0
358        precipstartdate2   = 0        precipstartdate2   = 0
359        precipperiod       = 0.0 _d 0        precipperiod       = 0.0 _d 0
360          precipconst        = 0.0 _d 0
361          precip_exfremo_intercept = 0.0 _d 0
362          precip_exfremo_slope = 0.0 _d 0
363    
364          snowprecipstartdate1   = 0
365          snowprecipstartdate2   = 0
366          snowprecipperiod       = 0.0 _d 0
367          snowprecipconst        = 0.0 _d 0
368          snowprecip_exfremo_intercept = 0.0 _d 0
369          snowprecip_exfremo_slope = 0.0 _d 0
370    
371        runoffstartdate1   = 0        runoffstartdate1   = 0
372        runoffstartdate2   = 0        runoffstartdate2   = 0
373        runoffperiod       = 0.0 _d 0        runoffperiod       = 0.0 _d 0
374          runoffconst        = 0.0 _d 0
375          runoff_exfremo_intercept = 0.0 _d 0
376          runoff_exfremo_slope = 0.0 _d 0
377    
378        ustressstartdate1  = 0        ustressstartdate1  = 0
379        ustressstartdate2  = 0        ustressstartdate2  = 0
380        ustressperiod      = 0.0 _d 0        ustressperiod      = 0.0 _d 0
381          ustressconst       = 0.0 _d 0
382          ustress_exfremo_intercept = 0.0 _d 0
383          ustress_exfremo_slope = 0.0 _d 0
384    
385        vstressstartdate1  = 0        vstressstartdate1  = 0
386        vstressstartdate2  = 0        vstressstartdate2  = 0
387        vstressperiod      = 0.0 _d 0        vstressperiod      = 0.0 _d 0
388          vstressconst       = 0.0 _d 0
389          vstress_exfremo_intercept = 0.0 _d 0
390          vstress_exfremo_slope = 0.0 _d 0
391    
392        uwindstartdate1    = 0        uwindstartdate1    = 0
393        uwindstartdate2    = 0        uwindstartdate2    = 0
394        uwindperiod        = 0.0 _d 0        uwindperiod        = 0.0 _d 0
395          uwindconst         = 0.0 _d 0
396          uwind_exfremo_intercept = 0.0 _d 0
397          uwind_exfremo_slope = 0.0 _d 0
398    
399        vwindstartdate1    = 0        vwindstartdate1    = 0
400        vwindstartdate2    = 0        vwindstartdate2    = 0
401        vwindperiod        = 0.0 _d 0        vwindperiod        = 0.0 _d 0
402          vwindconst         = 0.0 _d 0
403          vwind_exfremo_intercept = 0.0 _d 0
404          vwind_exfremo_slope = 0.0 _d 0
405    
406          wspeedstartdate1    = 0
407          wspeedstartdate2    = 0
408          wspeedperiod        = 0.0 _d 0
409          wspeedconst         = 0.0 _d 0
410          wspeed_exfremo_intercept = 0.0 _d 0
411          wspeed_exfremo_slope = 0.0 _d 0
412    
413        swfluxstartdate1   = 0        swfluxstartdate1   = 0
414        swfluxstartdate2   = 0        swfluxstartdate2   = 0
415        swfluxperiod       = 0.0 _d 0        swfluxperiod       = 0.0 _d 0
416          swfluxconst        = 0.0 _d 0
417          swflux_exfremo_intercept = 0.0 _d 0
418          swflux_exfremo_slope = 0.0 _d 0
419    
420        lwfluxstartdate1   = 0        lwfluxstartdate1   = 0
421        lwfluxstartdate2   = 0        lwfluxstartdate2   = 0
422        lwfluxperiod       = 0.0 _d 0        lwfluxperiod       = 0.0 _d 0
423          lwfluxconst        = 0.0 _d 0
424          lwflux_exfremo_intercept = 0.0 _d 0
425          lwflux_exfremo_slope = 0.0 _d 0
426    
427          swdownstartdate1   = 0
428          swdownstartdate2   = 0
429          swdownperiod       = 0.0 _d 0
430          swdownconst        = 0.0 _d 0
431          swdown_exfremo_intercept = 0.0 _d 0
432          swdown_exfremo_slope = 0.0 _d 0
433    
434          lwdownstartdate1   = 0
435          lwdownstartdate2   = 0
436          lwdownperiod       = 0.0 _d 0
437          lwdownconst        = 0.0 _d 0
438          lwdown_exfremo_intercept = 0.0 _d 0
439          lwdown_exfremo_slope = 0.0 _d 0
440    
441          apressurestartdate1    = 0
442          apressurestartdate2    = 0
443          apressureperiod        = 0.0 _d 0
444          apressureconst         = 0.0 _d 0
445          apressure_exfremo_intercept = 0.0 _d 0
446          apressure_exfremo_slope = 0.0 _d 0
447    
448          areamaskstartdate1    = 0
449          areamaskstartdate2    = 0
450          areamaskperiod        = 0.0 _d 0
451          areamaskTauRelax      = 0.0 _d 0
452          areamaskconst         = 0.0 _d 0
453          areamask_exfremo_intercept = 0. _d 0
454          areamask_exfremo_slope = 0. _d 0
455    
456          climsststartdate1  = 0
457          climsststartdate2  = 0
458          climsstperiod      = 0
459          climsstTauRelax    = 0.0 _d 0
460          climsstconst         = 0.0 _d 0
461          climsst_exfremo_intercept = 0.0 _d 0
462          climsst_exfremo_slope = 0.0 _d 0
463    
464          climsssstartdate1  = 0
465          climsssstartdate2  = 0
466          climsssperiod      = 0
467          climsssTauRelax    = 0.0 _d 0
468          climsssconst         = 0.0 _d 0
469          climsss_exfremo_intercept = 0.0 _d 0
470          climsss_exfremo_slope = 0.0 _d 0
471    
472          climustrstartdate1  = 0
473          climustrstartdate2  = 0
474          climustrperiod      = 0
475          climustrTauRelax    = 0.0 _d 0
476          climustrconst         = 0.0 _d 0
477          climustr_exfremo_intercept = 0.0 _d 0
478          climustr_exfremo_slope = 0.0 _d 0
479    
480          climvstrstartdate1  = 0
481          climvstrstartdate2  = 0
482          climvstrperiod      = 0
483          climvstrTauRelax    = 0.0 _d 0
484          climvstrconst         = 0.0 _d 0
485          climvstr_exfremo_intercept = 0.0 _d 0
486          climvstr_exfremo_slope = 0.0 _d 0
487    
488          sgrunoffstartdate1         = 0
489          sgrunoffstartdate2         = 0
490          sgrunoffstartdate          = 0.
491          sgrunoffperiod             = 0.0 _d 0
492          sgrunoffconst              = 0.0 _d 0
493          sgrunoff_exfremo_intercept = 0.0 _d 0
494          sgrunoff_exfremo_slope     = 0.0 _d 0
495          exf_inscal_sgrunoff        = 1. _d 0
496    
497          useOBCSYearlyFields = .FALSE.
498        obcsNstartdate1    = 0        obcsNstartdate1    = 0
499        obcsNstartdate2    = 0        obcsNstartdate2    = 0
500        obcsNperiod        = 0.0 _d 0        obcsNperiod        = 0.0 _d 0
   
501        obcsSstartdate1    = 0        obcsSstartdate1    = 0
502        obcsSstartdate2    = 0        obcsSstartdate2    = 0
503        obcsSperiod        = 0.0 _d 0        obcsSperiod        = 0.0 _d 0
   
504        obcsEstartdate1    = 0        obcsEstartdate1    = 0
505        obcsEstartdate2    = 0        obcsEstartdate2    = 0
506        obcsEperiod        = 0.0 _d 0        obcsEperiod        = 0.0 _d 0
   
507        obcsWstartdate1    = 0        obcsWstartdate1    = 0
508        obcsWstartdate2    = 0        obcsWstartdate2    = 0
509        obcsWperiod        = 0.0 _d 0        obcsWperiod        = 0.0 _d 0
510    
511        apressurestartdate1    = 0        siobNstartdate1    = UNSET_I
512        apressurestartdate2    = 0        siobNstartdate2    = UNSET_I
513        apressureperiod        = 0.0 _d 0        siobNperiod        = UNSET_RL
514          siobSstartdate1    = UNSET_I
515        windspeedstartdate1    = 0        siobSstartdate2    = UNSET_I
516        windspeedstartdate2    = 0        siobSperiod        = UNSET_RL
517        windspeedperiod        = 0.0 _d 0        siobEstartdate1    = UNSET_I
518          siobEstartdate2    = UNSET_I
519          siobEperiod        = UNSET_RL
520          siobWstartdate1    = UNSET_I
521          siobWstartdate2    = UNSET_I
522          siobWperiod        = UNSET_RL
523    
524          repeatPeriod       = 0.0 _d 0
525          windstressmax      = 2.0 _d 0
526    
527          exf_scal_BulkCdn   = 1.0  _d 0
528    
529        repeatPeriod           = 0.0 _d 0  C     Initialise freezing temperature of sea water
530          climtempfreeze     = -1.9 _d 0
531    
532    C     Data files.
 c     Data files.  
533        hfluxfile          = ' '        hfluxfile          = ' '
534        atempfile          = ' '        atempfile          = ' '
535        aqhfile            = ' '        aqhfile            = ' '
536          evapfile           = ' '
537        precipfile         = ' '        precipfile         = ' '
538          snowprecipfile     = ' '
539        sfluxfile          = ' '        sfluxfile          = ' '
540        runofffile         = ' '        runofffile         = ' '
541        ustressfile        = ' '        ustressfile        = ' '
542        vstressfile        = ' '        vstressfile        = ' '
543        uwindfile          = ' '        uwindfile          = ' '
544        vwindfile          = ' '        vwindfile          = ' '
545          wspeedfile         = ' '
546        swfluxfile         = ' '        swfluxfile         = ' '
547        lwfluxfile         = ' '        lwfluxfile         = ' '
548          swdownfile         = ' '
549          lwdownfile         = ' '
550        apressurefile      = ' '        apressurefile      = ' '
551        windspeedfile      = ' '        areamaskfile       = ' '
552          climsstfile        = ' '
553  c     Initialise the date arrays.        climsssfile        = ' '
554        do i = 1,4        climustrfile       = ' '
555           hfluxstartdate(i)    = 0        climvstrfile       = ' '
556           atempstartdate(i)    = 0  
557           aqhstartdate(i)      = 0  C     Start dates.
558           precipstartdate(i)   = 0        hfluxstartdate     = 0.
559           sfluxstartdate(i)    = 0        atempstartdate     = 0.
560           runoffstartdate(i)   = 0        aqhstartdate       = 0.
561           ustressstartdate(i)  = 0        evapstartdate      = 0.
562           vstressstartdate(i)  = 0        precipstartdate    = 0.
563           uwindstartdate(i)    = 0        snowprecipstartdate= 0.
564           vwindstartdate(i)    = 0        sfluxstartdate     = 0.
565           swfluxstartdate(i)   = 0        runoffstartdate    = 0.
566           lwfluxstartdate(i)   = 0        ustressstartdate   = 0.
567           obcsNstartdate(i)    = 0        vstressstartdate   = 0.
568           obcsSstartdate(i)    = 0        uwindstartdate     = 0.
569           obcsEstartdate(i)    = 0        vwindstartdate     = 0.
570           obcsWstartdate(i)    = 0        wspeedstartdate    = 0.
571           apressurestartdate(i)= 0        swfluxstartdate    = 0.
572           windspeedstartdate(i)= 0        lwfluxstartdate    = 0.
573        enddo        swdownstartdate    = 0.
574          lwdownstartdate    = 0.
575  c     Initialise file type and field precision        obcsNstartdate     = 0.
576        exf_iprec       = 32        obcsSstartdate     = 0.
577        exf_yftype      = 'RL'        obcsEstartdate     = 0.
578          obcsWstartdate     = 0.
579  c     scaling between exf units and MITgcm units        siobNstartdate     = 0.
580        scal_hfl       =  1. _d 0        siobSstartdate     = 0.
581        scal_ust       =  1. _d 0        siobEstartdate     = 0.
582        scal_vst       =  1. _d 0        siobWstartdate     = 0.
583        scal_swf       =  1. _d 0        apressurestartdate = 0.
584        scal_sst       =  1. _d 0        areamaskstartdate  = 0.
585        scal_sss       =  1. _d 0        climsststartdate   = 0.
586        scal_apressure =  1. _d 0        climsssstartdate   = 0.
587  #if (defined (ALLOW_BULKFORMULAE) && defined (ALLOW_ATM_TEMP))        climustrstartdate  = 0.
588        scal_prc       =  1. _d 0        climvstrstartdate  = 0.
589  #else  
590        scal_sfl       =  1. _d 0      C     Initialise file type and field precision
591  #endif        exf_iprec            = 32
592          exf_iprec_obcs       = UNSET_I
593  c     Check for the availability of the right calendar version.        exf_yftype           = 'RL'
594        if ( calendarversion .ne. usescalendarversion ) then        useExfYearlyFields   = .FALSE.
595           print*,' exf_readparms: You are not using the appropriate'        twoDigitYear         = .FALSE.
596           print*,'           version of the calendar package.'  
597           print*  C     Input scaling factors.
598           print*,' You are using Calendar version: ', calendarversion        exf_inscal_hflux     =  1. _d 0
599           print*,' Please use    Calendar version: ', usescalendarversion        exf_inscal_sflux     =  1. _d 0
600           stop ' stopped in exf_readparms.'        exf_inscal_ustress   =  1. _d 0
601        endif        exf_inscal_vstress   =  1. _d 0
602          exf_inscal_uwind     =  1. _d 0
603  c     Next, read the forcing data file.        exf_inscal_vwind     =  1. _d 0
604        call nml_filter( 'data.exf', scrunit1, myThid )        exf_inscal_wspeed    =  1. _d 0
605        if (scrunit1 .eq. 0) then        exf_inscal_swflux    =  1. _d 0
606           stop 'exf_readparms: reading namelist failed'        exf_inscal_lwflux    =  1. _d 0
607        end if        exf_inscal_precip    =  1. _d 0
608        read(  scrunit1, nml = exf_nml )        exf_inscal_snowprecip=  1. _d 0
609        close( scrunit1 )        exf_inscal_sst       =  1. _d 0
610          exf_inscal_sss       =  1. _d 0
611  c     Complete the start date specifications for the forcing        exf_inscal_atemp     =  1. _d 0
612  c     fields to get a complete calendar date array.        exf_offset_atemp     =  0. _d 0
613          exf_inscal_aqh       =  1. _d 0
614  c     check for consistency        exf_inscal_evap      =  1. _d 0
615          exf_inscal_apressure =  1. _d 0
616        if (.NOT.        exf_inscal_runoff    =  1. _d 0
617       &     (exf_iprec .EQ. 32 .OR. exf_iprec .EQ. 64)        exf_inscal_swdown    =  1. _d 0
618       &     ) then        exf_inscal_lwdown    =  1. _d 0
619           stop 'stop in exf_readparms: value of exf_iprec not allowed'        exf_inscal_climsst   =  1. _d 0
620        else if (.NOT.        exf_inscal_climsss   =  1. _d 0
621       &        (exf_yftype .EQ. 'RS' .OR.        exf_inscal_climustr  =  1. _d 0
622       &        exf_yftype .EQ. 'RL')        exf_inscal_climvstr  =  1. _d 0
623       &        ) then        exf_inscal_areamask  =  1. _d 0
624           stop 'stop in exf_readparms: value of exf_yftype not allowed'  
625        end if  C     Output scaling factors.
626          exf_outscal_hflux    =  1. _d 0
627  #ifdef ALLOW_RUNOFF        exf_outscal_sflux    =  1. _d 0
628        call cal_FullDate(  runoffstartdate1,  runoffstartdate2,        exf_outscal_ustress  =  1. _d 0
629       &                    runoffstartdate,            mythid )        exf_outscal_vstress  =  1. _d 0
630  #endif        exf_outscal_swflux   =  1. _d 0
631          exf_outscal_sst      =  1. _d 0
632  #ifdef ALLOW_BULKFORMULAE        exf_outscal_sss      =  1. _d 0
633          exf_outscal_apressure=  1. _d 0
634  #ifdef ALLOW_ATM_TEMP        exf_outscal_areamask =  1. _d 0
635        call cal_FullDate(   atempstartdate1,   atempstartdate2,  
636       &                     atempstartdate,            mythid )  #ifdef USE_EXF_INTERPOLATION
637        call cal_FullDate(     aqhstartdate1,     aqhstartdate2,  C--   set default input location to match (in case of simple Lat-Lonp grid)
638       &                       aqhstartdate,            mythid )  C     model grid cell-center position (leading to trivial interpolation)
639        call cal_FullDate(  swfluxstartdate1,  swfluxstartdate2,        inp_lon0 = xgOrigin + delX(1)*exf_half
640       &                    swfluxstartdate,            mythid )        inp_lat0 = ygOrigin + delY(1)*exf_half
641        call cal_FullDate(  lwfluxstartdate1,  lwfluxstartdate2,        inp_dLon = delX(1)
642       &                    lwfluxstartdate,            mythid )        inp_dLat = delY(1)
643        call cal_FullDate(  precipstartdate1,  precipstartdate2,  
644       &                    precipstartdate,            mythid )        ustress_lon0   = inp_lon0
645        call cal_FullDate(windspeedstartdate1, windspeedstartdate2,        uwind_lon0     = inp_lon0
646       &                     windspeedstartdate,            mythid )        vstress_lon0   = inp_lon0
647  #else        hflux_lon0     = inp_lon0
648        call cal_FullDate(   hfluxstartdate1,   hfluxstartdate2,        sflux_lon0     = inp_lon0
649       &                     hfluxstartdate,            mythid )        swflux_lon0    = inp_lon0
650        call cal_FullDate(   sfluxstartdate1,  sfluxstartdate2,        runoff_lon0    = inp_lon0
651       &                     sfluxstartdate,           mythid )        atemp_lon0     = inp_lon0
652  #ifdef ALLOW_KPP        aqh_lon0       = inp_lon0
653        call cal_FullDate(  swfluxstartdate1,  swfluxstartdate2,        evap_lon0      = inp_lon0
654       &                    swfluxstartdate,            mythid )        precip_lon0    = inp_lon0
655  #endif        snowprecip_lon0= inp_lon0
656          vwind_lon0     = inp_lon0
657  #endif        wspeed_lon0    = inp_lon0
658          lwflux_lon0    = inp_lon0
659  #ifdef ALLOW_ATM_WIND        swdown_lon0    = inp_lon0
660        call cal_FullDate(   uwindstartdate1,   uwindstartdate2,        lwdown_lon0    = inp_lon0
661       &                     uwindstartdate,            mythid )        apressure_lon0 = inp_lon0
662        call cal_FullDate(   vwindstartdate1,   vwindstartdate2,        areamask_lon0  = inp_lon0
663       &                     vwindstartdate,            mythid )        vstress_lat0   = inp_lat0
664  #else        vwind_lat0     = inp_lat0
665        call cal_FullDate( ustressstartdate1, ustressstartdate2,        wspeed_lat0    = inp_lat0
666       &                   ustressstartdate,            mythid )        ustress_lat0   = inp_lat0
667        call cal_FullDate( vstressstartdate1, vstressstartdate2,        hflux_lat0     = inp_lat0
668       &                   vstressstartdate,            mythid )        sflux_lat0     = inp_lat0
669  #endif        runoff_lat0    = inp_lat0
670          swflux_lat0    = inp_lat0
671  #else        atemp_lat0     = inp_lat0
672        call cal_FullDate(   hfluxstartdate1,  hfluxstartdate2,        aqh_lat0       = inp_lat0
673       &                     hfluxstartdate,           mythid )        evap_lat0      = inp_lat0
674        call cal_FullDate(   sfluxstartdate1,  sfluxstartdate2,        precip_lat0    = inp_lat0
675       &                     sfluxstartdate,           mythid )        snowprecip_lat0= inp_lat0
676        call cal_FullDate( ustressstartdate1, ustressstartdate2,        uwind_lat0     = inp_lat0
677       &                   ustressstartdate,            mythid )        lwflux_lat0    = inp_lat0
678        call cal_FullDate( vstressstartdate1, vstressstartdate2,        swdown_lat0    = inp_lat0
679       &                   vstressstartdate,            mythid )        lwdown_lat0    = inp_lat0
680  #ifdef ALLOW_KPP        apressure_lat0 = inp_lat0
681        call cal_FullDate(  swfluxstartdate1,  swfluxstartdate2,        areamask_lat0  = inp_lat0
682       &                    swfluxstartdate,            mythid )        ustress_nlon   = gridNx
683  #endif        ustress_nlat   = gridNy
684          vstress_nlon   = gridNx
685  #endif        vstress_nlat   = gridNy
686          hflux_nlon     = gridNx
687          hflux_nlat     = gridNy
688          sflux_nlon     = gridNx
689          sflux_nlat     = gridNy
690          swflux_nlon    = gridNx
691          swflux_nlat    = gridNy
692          runoff_nlon    = gridNx
693          runoff_nlat    = gridNy
694          atemp_nlon     = gridNx
695          atemp_nlat     = gridNy
696          aqh_nlon       = gridNx
697          aqh_nlat       = gridNy
698          evap_nlon      = gridNx
699          evap_nlat      = gridNy
700          precip_nlon    = gridNx
701          snowprecip_nlon= gridNx
702          precip_nlat    = gridNy
703          snowprecip_nlat= gridNy
704          uwind_nlon     = gridNx
705          uwind_nlat     = gridNy
706          vwind_nlon     = gridNx
707          vwind_nlat     = gridNy
708          wspeed_nlon    = gridNx
709          wspeed_nlat    = gridNy
710          lwflux_nlon    = gridNx
711          lwflux_nlat    = gridNy
712          swdown_nlon    = gridNx
713          swdown_nlat    = gridNy
714          lwdown_nlon    = gridNx
715          lwdown_nlat    = gridNy
716          apressure_nlon = gridNx
717          apressure_nlat = gridNy
718          areamask_nlon  = gridNx
719          areamask_nlat  = gridNy
720          ustress_lon_inc   = inp_dLon
721          vstress_lon_inc   = inp_dLon
722          hflux_lon_inc     = inp_dLon
723          sflux_lon_inc     = inp_dLon
724          swflux_lon_inc    = inp_dLon
725          runoff_lon_inc    = inp_dLon
726          atemp_lon_inc     = inp_dLon
727          aqh_lon_inc       = inp_dLon
728          evap_lon_inc      = inp_dLon
729          precip_lon_inc    = inp_dLon
730          snowprecip_lon_inc= inp_dLon
731          uwind_lon_inc     = inp_dLon
732          vwind_lon_inc     = inp_dLon
733          wspeed_lon_inc    = inp_dLon
734          lwflux_lon_inc    = inp_dLon
735          swdown_lon_inc    = inp_dLon
736          lwdown_lon_inc    = inp_dLon
737          apressure_lon_inc = inp_dLon
738          areamask_lon_inc  = inp_dLon
739    
740          climsst_lon0    = inp_lon0
741          climsss_lon0    = inp_lon0
742          climustr_lon0   = inp_lon0
743          climvstr_lon0   = inp_lon0
744          climsst_lat0    = inp_lat0
745          climsss_lat0    = inp_lat0
746          climustr_lat0   = inp_lat0
747          climvstr_lat0   = inp_lat0
748          climsst_nlon    = gridNx
749          climsst_nlat    = gridNy
750          climsss_nlon    = gridNx
751          climsss_nlat    = gridNy
752          climustr_nlon   = gridNx
753          climustr_nlat   = gridNy
754          climvstr_nlon   = gridNx
755          climvstr_nlat   = gridNy
756          climsst_lon_inc = inp_dLon
757          climsss_lon_inc = inp_dLon
758          climustr_lon_inc= inp_dLon
759          climvstr_lon_inc= inp_dLon
760    
761          DO j=1,MAX_LAT_INC
762            IF (j.LT.gridNy) THEN
763              inp_dLat = (delY(j) + delY(j+1))*exf_half
764            ELSE
765              inp_dLat = 0.
766            ENDIF
767            ustress_lat_inc(j)   = inp_dLat
768            vstress_lat_inc(j)   = inp_dLat
769            hflux_lat_inc(j)     = inp_dLat
770            sflux_lat_inc(j)     = inp_dLat
771            swflux_lat_inc(j)    = inp_dLat
772            runoff_lat_inc(j)    = inp_dLat
773            atemp_lat_inc(j)     = inp_dLat
774            aqh_lat_inc(j)       = inp_dLat
775            evap_lat_inc(j)      = inp_dLat
776            precip_lat_inc(j)    = inp_dLat
777            snowprecip_lat_inc(j)= inp_dLat
778            uwind_lat_inc(j)     = inp_dLat
779            vwind_lat_inc(j)     = inp_dLat
780            wspeed_lat_inc(j)    = inp_dLat
781            lwflux_lat_inc(j)    = inp_dLat
782            swdown_lat_inc(j)    = inp_dLat
783            lwdown_lat_inc(j)    = inp_dLat
784            apressure_lat_inc(j) = inp_dLat
785            areamask_lat_inc(j)  = inp_dLat
786            climsst_lat_inc(j)   = inp_dLat
787            climsss_lat_inc(j)   = inp_dLat
788            climustr_lat_inc(j)  = inp_dLat
789            climvstr_lat_inc(j)  = inp_dLat
790          ENDDO
791    
792          ustress_interpMethod   = 12
793          vstress_interpMethod   = 22
794          hflux_interpMethod     =  1
795          sflux_interpMethod     =  1
796          swflux_interpMethod    =  1
797          runoff_interpMethod    =  1
798          atemp_interpMethod     =  1
799          aqh_interpMethod       =  1
800          evap_interpMethod      =  1
801          precip_interpMethod    =  1
802          snowprecip_interpMethod=  1
803          uwind_interpMethod     = 12
804          vwind_interpMethod     = 22
805          wspeed_interpMethod    =  1
806          lwflux_interpMethod    =  1
807          swdown_interpMethod    =  1
808          lwdown_interpMethod    =  1
809          apressure_interpMethod =  1
810          areamask_interpMethod  =  1
811          climsst_interpMethod   =  2
812          climsss_interpMethod   =  2
813          climustr_interpMethod  = 12
814          climvstr_interpMethod  = 22
815    
816    #endif /* USE_EXF_INTERPOLATION */
817    
818    C     Next, read the forcing data file.
819          WRITE(msgBuf,'(A)') 'EXF_READPARMS: opening data.exf'
820          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
821         &     SQUEEZE_RIGHT , 1)
822    
823          CALL OPEN_COPY_DATA_FILE(
824         I                          'data.exf', 'EXF_READPARMS',
825         O                          iUnit,
826         I                          myThid )
827    
828          WRITE(msgBuf,'(A)')
829         &     'EXF_READPARMS: reading EXF_NML_01'
830          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
831         &     SQUEEZE_RIGHT , 1)
832          READ(  iUnit, nml = EXF_NML_01 )
833          WRITE(msgBuf,'(A)')
834         &     'EXF_READPARMS: reading EXF_NML_02'
835          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
836         &     SQUEEZE_RIGHT , 1)
837          READ(  iUnit, nml = EXF_NML_02 )
838          WRITE(msgBuf,'(A)')
839         &     'EXF_READPARMS: reading EXF_NML_03'
840          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
841         &     SQUEEZE_RIGHT , 1)
842          READ(  iUnit, nml = EXF_NML_03 )
843    #ifdef USE_EXF_INTERPOLATION
844          WRITE(msgBuf,'(A)')
845         &     'EXF_READPARMS: reading EXF_NML_04'
846          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
847         &     SQUEEZE_RIGHT , 1)
848          READ(  iUnit, nml = EXF_NML_04 )
849    #endif /* USE_EXF_INTERPOLATION */
850    
851    #ifdef ALLOW_ICEFRONT
852          IF ( useIcefront ) THEN
853           WRITE(msgBuf,'(A)')
854         &      'EXF_READPARMS: reading EXF_NML_SGRUNOFF'
855           CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
856         &      SQUEEZE_RIGHT , 1)
857           READ(  iUnit, nml = EXF_NML_SGRUNOFF )
858          ENDIF
859    #endif /* ALLOW_ICEFRONT */
860    
861  #ifdef ALLOW_OBCS  #ifdef ALLOW_OBCS
862  #ifdef ALLOW_OBCS_NORTH        IF ( useOBCS ) THEN
863        call cal_FullDate(  obcsNstartdate1,  obcsNstartdate2,         WRITE(msgBuf,'(A)')
864       &                    obcsNstartdate,           mythid )       &      'EXF_READPARMS: reading EXF_NML_OBCS'
865  #endif         CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
866  #ifdef ALLOW_OBCS_SOUTH       &      SQUEEZE_RIGHT , 1)
867        call cal_FullDate(  obcsSstartdate1,  obcsSstartdate2,         READ(  iUnit, nml = EXF_NML_OBCS )
868       &                    obcsSstartdate,           mythid )        ENDIF
869  #endif         IF(siobNstartdate1.EQ.UNSET_I ) siobNstartdate1=obcsNstartdate1
870  #ifdef ALLOW_OBCS_EAST         IF(siobNstartdate2.EQ.UNSET_I ) siobNstartdate2=obcsNstartdate2
871        call cal_FullDate(  obcsEstartdate1,  obcsEstartdate2,         IF(siobNperiod    .EQ.UNSET_RL) siobNperiod    =obcsNperiod
872       &                    obcsEstartdate,           mythid )         IF(siobSstartdate1.EQ.UNSET_I ) siobSstartdate1=obcsSstartdate1
873  #endif         IF(siobSstartdate2.EQ.UNSET_I ) siobSstartdate2=obcsSstartdate2
874  #ifdef ALLOW_OBCS_WEST         IF(siobSperiod    .EQ.UNSET_RL) siobSperiod    =obcsSperiod
875        call cal_FullDate(  obcsWstartdate1,  obcsWstartdate2,         IF(siobEstartdate1.EQ.UNSET_I ) siobEstartdate1=obcsEstartdate1
876       &                    obcsWstartdate,           mythid )         IF(siobEstartdate2.EQ.UNSET_I ) siobEstartdate2=obcsEstartdate2
877  #endif         IF(siobEperiod    .EQ.UNSET_RL) siobEperiod    =obcsEperiod
878  #endif         IF(siobWstartdate1.EQ.UNSET_I ) siobWstartdate1=obcsWstartdate1
879           IF(siobWstartdate2.EQ.UNSET_I ) siobWstartdate2=obcsWstartdate2
880  #ifdef ATMOSPHERIC_LOADING         IF(siobWperiod    .EQ.UNSET_RL) siobWperiod    =obcsWperiod
881        call cal_FullDate(   apressurestartdate1, apressurestartdate2,  
882       &                     apressurestartdate,          mythid )         IF(exf_iprec_obcs .EQ. UNSET_I) exf_iprec_obcs =exf_iprec
883  #endif  #endif /* ALLOW_OBCS */
884    
885        _END_MASTER( mythid )        WRITE(msgBuf,'(A)')
886         &     'EXF_READPARMS: finished reading data.exf'
887          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
888         &                SQUEEZE_RIGHT , 1)
889    
890          CLOSE( iUnit )
891    
892    C--   Retired parameters
893          IF ( exf_yftype.NE.'RL' ) THEN
894           STOP 'S/R EXF_READPARAMS: value of exf_yftype not allowed'
895          ENDIF
896    
897    C--   Derive other parameters:
898          hq = ht
899          stressIsOnCgrid = readStressOnCgrid
900    #if ( defined (ALLOW_BULKFORMULAE) )
901          IF ( useAtmWind ) stressIsOnCgrid = .FALSE.
902    #endif
903    #ifdef USE_EXF_INTERPOLATION
904          IF ( (ustress_interpMethod.GE.1 .AND. ustressfile.NE.' ') .OR.
905         &     (vstress_interpMethod.GE.1 .AND. vstressfile.NE.' ') )
906         &   stressIsOnCgrid = .FALSE.
907    #endif /* USE_EXF_INTERPOLATION */
908    
909          IF ( select_ZenAlbedo.GT.0 ) THEN
910               useExfZenAlbedo=.TRUE.
911          ENDIf
912    
913    C--   Overwrite tauThetaClimRelax but stop if already set.
914    C- Note: need this, even if EXF option ALLOW_CLIMSST_RELAXATION is undef;
915    C        this prevents to apply relaxation towards potentially wrong SST since,
916    C        with EXF, we skip the update of loaded SST in EXTERNAL_FIELDS_LOAD.
917    C- Note2: let s see whether we can put this back under ifdef
918    C        ALLOW_CLIMSST_RELAXATION, but always call EXTERNAL_FIELDS_LOAD.
919    C        If ALLOW_CLIMSST_RELAXATION is undef, clim.relaxation could still
920    C        be done outside of exf.
921    #ifdef ALLOW_CLIMSST_RELAXATION
922          IF ( tauThetaClimRelax.NE.0. _d 0 ) THEN
923            WRITE(msgBuf,'(2A)') 'EXF_READPARMS: ',
924         &   'with EXF, cannot use "tauThetaClimRelax" in "data"'
925            CALL PRINT_ERROR( msgBuf, myThid )
926            WRITE(msgBuf,'(2A)') 'since SST relax. is handled by EXF',
927         &   ' (data.exf, "climsstTauRelax")'
928            CALL PRINT_ERROR( msgBuf, myThid )
929            STOP 'ABNORMAL END: S/R EXF_READPARMS'
930          ENDIF
931          tauThetaClimRelax = climsstTauRelax
932    #endif
933    
934    #ifdef ALLOW_CLIMSSS_RELAXATION
935    C--   Overwrite tauSaltClimRelax but stop if already set.
936          IF ( tauSaltClimRelax.NE.0. _d 0 ) THEN
937            WRITE(msgBuf,'(2A)') 'EXF_READPARMS: ',
938         &   'with EXF, cannot use "tauSaltClimRelax" in "data"'
939            CALL PRINT_ERROR( msgBuf, myThid )
940            WRITE(msgBuf,'(2A)') 'since SSS relax. is handled by EXF',
941         &   ' (data.exf, "climsssTauRelax")'
942            CALL PRINT_ERROR( msgBuf, myThid )
943            STOP 'ABNORMAL END: S/R EXF_READPARMS'
944          ENDIF
945          tauSaltClimRelax = climsssTauRelax
946    #endif
947    
948    C     Complete the start date specifications for the forcing
949    C     fields to get a complete calendar date array.
950    C     => moved to EXF_INIT_FIXED
951    
952          _END_MASTER( myThid )
953        _BARRIER        _BARRIER
954    
955  c--   Summarize the External forcing's setup.        RETURN
956        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.77

  ViewVC Help
Powered by ViewVC 1.1.22