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

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

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


Revision 1.16 - (hide annotations) (download)
Wed Mar 3 05:17:45 2004 UTC (20 years, 3 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube5, checkpoint52l_post, checkpoint52m_post
Changes since 1.15: +3 -2 lines
o no restoring terms under ice for pkg/seaice
o modfied EXF_EXTERNAL_FLUXES option
o added exf_albedo parameter

1 dimitri 1.16 C $Header: /usr/local/gcmpack/MITgcm/pkg/exf/exf_readparms.F,v 1.15 2004/02/26 19:34:34 heimbach Exp $
2 jmc 1.11 C $Name: $
3 heimbach 1.1
4 edhill 1.12 #include "EXF_OPTIONS.h"
5 heimbach 1.3 #ifdef ALLOW_OBCS
6     # include "OBCS_OPTIONS.h"
7     #endif
8 heimbach 1.1
9 heimbach 1.3 subroutine exf_readparms( mythid )
10 heimbach 1.1
11     c ==================================================================
12     c SUBROUTINE exf_readparms
13     c ==================================================================
14     c
15     c o This routine initialises the package that calculates external
16     c forcing fields for a given timestep of the MITgcmUV. Parameters
17     c for this package are set in "data.externalforcing". Some additional
18 edhill 1.12 c precompiler switches have to be specified in "EXF_OPTIONS.h".
19 heimbach 1.1 c
20     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
21     c
22     c changed: Christian Eckert eckert@mit.edu 11-Jan-2000
23     c - Restructured the code in order to create a package
24     c for the MITgcmUV.
25     c Christian Eckert eckert@mit.edu 12-Feb-2000
26     c - Changed Routine names (package prefix: exf_)
27 heimbach 1.2 c changed: Patrick Heimbach, heimbach@mit.edu 04-May-2000
28 heimbach 1.1 c - changed the handling of precip and sflux with respect
29     c to CPP options ALLOW_BULKFORMULAE and ALLOW_ATM_TEMP
30     c changed: Ralf.Giering@FastOpt.de 25-Mai-20000
31 heimbach 1.2 c - moved relaxation and climatology to extra routines
32 heimbach 1.1 c Patrick Heimbach, heimbach@mit.edu 04-May-2000
33     c - added obcs parameters
34 heimbach 1.2 c changed: Virginie Thierry, vthierry@ucsd.edu 04-June-2001
35     c - added new obcs parameters (for each boundaries)
36 heimbach 1.3 c included runoff D. Stammer, Nov. 25, 2001
37     c included pressure forcing. heimbach@mit.edu 05-Nov-2002
38 dimitri 1.5 c added "repeatPeriod" for cycling of forcing datasets 19-Dec-2002
39 dimitri 1.6 c mods for pkg/seaice: menemenlis@jpl.nasa.gov 20-Dec-2002
40 heimbach 1.1 c
41     c ==================================================================
42     c SUBROUTINE exf_readparms
43     c ==================================================================
44    
45     implicit none
46    
47     c == global variables ==
48    
49     #include "EEPARAMS.h"
50     #include "SIZE.h"
51 heimbach 1.15 #include "PARAMS.h"
52    
53 heimbach 1.1 #include "cal.h"
54     #include "exf.h"
55     #include "exf_param.h"
56     #include "exf_constants.h"
57    
58     c == routine arguments ==
59    
60     integer mythid
61    
62     c == local variables ==
63    
64     integer i
65 dimitri 1.13 integer date_array(4), difftime(4)
66 heimbach 1.1
67     c == external ==
68    
69     integer ilnblnk
70     external ilnblnk
71    
72     c == end of interface ==
73    
74     c Surface flux data.
75     namelist /exf_nml/
76 dimitri 1.16 & repeatPeriod, exf_albedo,
77 heimbach 1.1 & hfluxstartdate1, hfluxstartdate2, hfluxperiod,
78     & atempstartdate1, atempstartdate2, atempperiod,
79     & aqhstartdate1, aqhstartdate2, aqhperiod,
80     & sfluxstartdate1, sfluxstartdate2, sfluxperiod,
81 dimitri 1.5 & evapstartdate1, evapstartdate2, evapperiod,
82 heimbach 1.1 & precipstartdate1, precipstartdate2, precipperiod,
83 heimbach 1.3 & runoffstartdate1, runoffstartdate2, runoffperiod,
84 heimbach 1.1 & ustressstartdate1, ustressstartdate2, ustressperiod,
85     & vstressstartdate1, vstressstartdate2, vstressperiod,
86     & uwindstartdate1, uwindstartdate2, uwindperiod,
87     & vwindstartdate1, vwindstartdate2, vwindperiod,
88     & swfluxstartdate1, swfluxstartdate2, swfluxperiod,
89     & lwfluxstartdate1, lwfluxstartdate2, lwfluxperiod,
90 dimitri 1.6 & swdownstartdate1, swdownstartdate2, swdownperiod,
91     & lwdownstartdate1, lwdownstartdate2, lwdownperiod,
92 heimbach 1.2 & obcsNstartdate1, obcsNstartdate2, obcsNperiod,
93     & obcsSstartdate1, obcsSstartdate2, obcsSperiod,
94     & obcsEstartdate1, obcsEstartdate2, obcsEperiod,
95     & obcsWstartdate1, obcsWstartdate2, obcsWperiod,
96 heimbach 1.3 &apressurestartdate1,apressurestartdate2,apressureperiod,
97 heimbach 1.1 & hfluxfile, atempfile, aqhfile,
98 heimbach 1.3 & sfluxfile, precipfile, runofffile,
99 dimitri 1.5 & ustressfile, vstressfile, evapfile,
100 heimbach 1.3 & uwindfile, vwindfile,
101     & swfluxfile, lwfluxfile, apressurefile,
102 dimitri 1.6 & swdownfile, lwdownfile,
103 heimbach 1.3 & exf_iprec, exf_yftype,
104 dimitri 1.14 & exf_inscal_hflux, exf_inscal_sflux,
105     & exf_inscal_ustress, exf_inscal_vstress,
106     & exf_inscal_uwind, exf_inscal_vwind, exf_inscal_evap,
107     & exf_inscal_atemp, exf_offset_atemp, exf_inscal_aqh,
108     & exf_inscal_sst, exf_inscal_sss,
109     & exf_inscal_swflux, exf_inscal_lwflux, exf_inscal_precip,
110     & exf_inscal_runoff, exf_inscal_apressure,
111 heimbach 1.8 & exf_inscal_swdown, exf_inscal_lwdown,
112     & exf_outscal_hflux, exf_outscal_ustress, exf_outscal_vstress,
113 dimitri 1.14 & exf_outscal_swflux, exf_outscal_sst, exf_outscal_sss,
114 heimbach 1.8 & exf_outscal_sflux, exf_outscal_apressure,
115 heimbach 1.7 & hfluxconst,
116     & atempconst,
117     & aqhconst,
118     & sfluxconst,
119     & evapconst,
120     & precipconst,
121     & runoffconst,
122     & ustressconst,
123     & vstressconst,
124     & uwindconst,
125     & vwindconst,
126     & swfluxconst,
127     & lwfluxconst,
128     & swdownconst,
129     & lwdownconst,
130 dimitri 1.10 & apressureconst
131 dimitri 1.9 #ifdef USE_EXF_INTERPOLATION
132 jmc 1.11 & ,ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
133 dimitri 1.9 & ustress_nlon, ustress_nlat,
134 jmc 1.11 & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
135 dimitri 1.9 & vstress_nlon, vstress_nlat,
136 jmc 1.11 & hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
137 dimitri 1.9 & hflux_nlon, hflux_nlat,
138 jmc 1.11 & sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
139 dimitri 1.9 & sflux_nlon, sflux_nlat,
140 jmc 1.11 & swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
141 dimitri 1.9 & swflux_nlon, swflux_nlat,
142 jmc 1.11 & runoff_lon0, runoff_lon_inc, runoff_lat0, runoff_lat_inc,
143 dimitri 1.9 & runoff_nlon, runoff_nlat,
144 jmc 1.11 & atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
145 dimitri 1.9 & atemp_nlon, atemp_nlat,
146 jmc 1.11 & aqh_lon0, aqh_lon_inc, aqh_lat0, aqh_lat_inc,
147 dimitri 1.9 & aqh_nlon, aqh_nlat,
148 jmc 1.11 & evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
149 dimitri 1.9 & evap_nlon, evap_nlat,
150 jmc 1.11 & precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
151 dimitri 1.9 & precip_nlon, precip_nlat,
152 jmc 1.11 & uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
153 dimitri 1.9 & uwind_nlon, uwind_nlat,
154 jmc 1.11 & vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
155 dimitri 1.9 & vwind_nlon, vwind_nlat,
156 jmc 1.11 & lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
157 dimitri 1.9 & lwflux_nlon, lwflux_nlat,
158 jmc 1.11 & swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
159 dimitri 1.9 & swdown_nlon, swdown_nlat,
160 jmc 1.11 & lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
161 dimitri 1.9 & lwdown_nlon, lwdown_nlat,
162 jmc 1.11 & apressure_lon0,apressure_lon_inc,
163 dimitri 1.9 & apressure_lat0,apressure_lat_inc,
164     & apressure_nlon,apressure_nlat
165     #endif
166 heimbach 1.1
167     _BEGIN_MASTER(mythid)
168    
169     c Set default values.
170    
171     c Calendar data.
172     hfluxstartdate1 = 0
173     hfluxstartdate2 = 0
174     hfluxperiod = 0.0 _d 0
175 heimbach 1.7 hfluxconst = 0.0 _d 0
176 heimbach 1.1
177     atempstartdate1 = 0
178     atempstartdate2 = 0
179     atempperiod = 0.0 _d 0
180 heimbach 1.15 atempconst = celsius2K
181 heimbach 1.1
182     aqhstartdate1 = 0
183     aqhstartdate2 = 0
184     aqhperiod = 0.0 _d 0
185 heimbach 1.7 aqhconst = 0.0 _d 0
186 heimbach 1.1
187     sfluxstartdate1 = 0
188     sfluxstartdate2 = 0
189     sfluxperiod = 0.0 _d 0
190 heimbach 1.7 sfluxconst = 0.0 _d 0
191 heimbach 1.1
192 dimitri 1.5 evapstartdate1 = 0
193     evapstartdate2 = 0
194     evapperiod = 0.0 _d 0
195 heimbach 1.7 evapconst = 0.0 _d 0
196 dimitri 1.5
197 heimbach 1.1 precipstartdate1 = 0
198     precipstartdate2 = 0
199     precipperiod = 0.0 _d 0
200 heimbach 1.7 precipconst = 0.0 _d 0
201 heimbach 1.1
202 heimbach 1.3 runoffstartdate1 = 0
203     runoffstartdate2 = 0
204     runoffperiod = 0.0 _d 0
205 heimbach 1.7 runoffconst = 0.0 _d 0
206 heimbach 1.3
207 heimbach 1.1 ustressstartdate1 = 0
208     ustressstartdate2 = 0
209     ustressperiod = 0.0 _d 0
210 heimbach 1.7 ustressconst = 0.0 _d 0
211 heimbach 1.1
212     vstressstartdate1 = 0
213     vstressstartdate2 = 0
214     vstressperiod = 0.0 _d 0
215 heimbach 1.7 vstressconst = 0.0 _d 0
216 heimbach 1.1
217     uwindstartdate1 = 0
218     uwindstartdate2 = 0
219     uwindperiod = 0.0 _d 0
220 heimbach 1.7 uwindconst = 0.0 _d 0
221 heimbach 1.1
222     vwindstartdate1 = 0
223     vwindstartdate2 = 0
224     vwindperiod = 0.0 _d 0
225 heimbach 1.7 vwindconst = 0.0 _d 0
226 heimbach 1.1
227     swfluxstartdate1 = 0
228     swfluxstartdate2 = 0
229     swfluxperiod = 0.0 _d 0
230 heimbach 1.7 swfluxconst = 0.0 _d 0
231 heimbach 1.1
232     lwfluxstartdate1 = 0
233     lwfluxstartdate2 = 0
234     lwfluxperiod = 0.0 _d 0
235 heimbach 1.7 lwfluxconst = 0.0 _d 0
236 heimbach 1.1
237 dimitri 1.6 swdownstartdate1 = 0
238     swdownstartdate2 = 0
239     swdownperiod = 0.0 _d 0
240 heimbach 1.7 swdownconst = 0.0 _d 0
241 dimitri 1.6
242     lwdownstartdate1 = 0
243     lwdownstartdate2 = 0
244     lwdownperiod = 0.0 _d 0
245 heimbach 1.7 lwdownconst = 0.0 _d 0
246 dimitri 1.6
247 heimbach 1.2 obcsNstartdate1 = 0
248     obcsNstartdate2 = 0
249     obcsNperiod = 0.0 _d 0
250    
251     obcsSstartdate1 = 0
252     obcsSstartdate2 = 0
253     obcsSperiod = 0.0 _d 0
254    
255     obcsEstartdate1 = 0
256     obcsEstartdate2 = 0
257     obcsEperiod = 0.0 _d 0
258    
259     obcsWstartdate1 = 0
260     obcsWstartdate2 = 0
261     obcsWperiod = 0.0 _d 0
262 heimbach 1.1
263 heimbach 1.3 apressurestartdate1 = 0
264     apressurestartdate2 = 0
265     apressureperiod = 0.0 _d 0
266 heimbach 1.7 apressureconst = 0.0 _d 0
267 cheisey 1.4
268     repeatPeriod = 0.0 _d 0
269 dimitri 1.16 exf_albedo = 0.1 _d 0
270 cheisey 1.4
271 heimbach 1.1 c Data files.
272     hfluxfile = ' '
273     atempfile = ' '
274     aqhfile = ' '
275 dimitri 1.5 evapfile = ' '
276 heimbach 1.1 precipfile = ' '
277     sfluxfile = ' '
278 heimbach 1.3 runofffile = ' '
279 heimbach 1.1 ustressfile = ' '
280     vstressfile = ' '
281     uwindfile = ' '
282     vwindfile = ' '
283     swfluxfile = ' '
284     lwfluxfile = ' '
285 dimitri 1.6 swdownfile = ' '
286     lwdownfile = ' '
287 heimbach 1.3 apressurefile = ' '
288 heimbach 1.1
289 dimitri 1.13 c Start dates.
290     hfluxstartdate = 0
291     atempstartdate = 0
292     aqhstartdate = 0
293     evapstartdate = 0
294     precipstartdate = 0
295     sfluxstartdate = 0
296     runoffstartdate = 0
297     ustressstartdate = 0
298     vstressstartdate = 0
299     uwindstartdate = 0
300     vwindstartdate = 0
301     swfluxstartdate = 0
302     lwfluxstartdate = 0
303     swdownstartdate = 0
304     lwdownstartdate = 0
305     obcsNstartdate = 0
306     obcsSstartdate = 0
307     obcsEstartdate = 0
308     obcsWstartdate = 0
309     apressurestartdate = 0
310 heimbach 1.1
311     c Initialise file type and field precision
312     exf_iprec = 32
313     exf_yftype = 'RL'
314    
315 dimitri 1.6 c Input scaling factors.
316 heimbach 1.8 exf_inscal_hflux = 1. _d 0
317     exf_inscal_sflux = 1. _d 0
318     exf_inscal_ustress = 1. _d 0
319     exf_inscal_vstress = 1. _d 0
320     exf_inscal_uwind = 1. _d 0
321     exf_inscal_vwind = 1. _d 0
322     exf_inscal_swflux = 1. _d 0
323     exf_inscal_lwflux = 1. _d 0
324     exf_inscal_precip = 1. _d 0
325 dimitri 1.6 exf_inscal_sst = 1. _d 0
326     exf_inscal_sss = 1. _d 0
327 heimbach 1.8 exf_inscal_atemp = 1. _d 0
328 dimitri 1.14 exf_offset_atemp = 0. _d 0
329 heimbach 1.8 exf_inscal_aqh = 1. _d 0
330     exf_inscal_evap = 1. _d 0
331 dimitri 1.6 exf_inscal_apressure = 1. _d 0
332     cds convert runoff from m/yr to m/s and change sign.
333     exf_inscal_runoff = -1.0/(86400.*365.0)
334 heimbach 1.8 exf_inscal_swdown = 1. _d 0
335     exf_inscal_lwdown = 1. _d 0
336 dimitri 1.6
337     c Output scaling factors.
338 heimbach 1.8 exf_outscal_hflux = 1. _d 0
339     exf_outscal_sflux = 1. _d 0
340     exf_outscal_ustress = 1. _d 0
341     exf_outscal_vstress = 1. _d 0
342     exf_outscal_swflux = 1. _d 0
343 dimitri 1.6 exf_outscal_sst = 1. _d 0
344     exf_outscal_sss = 1. _d 0
345     exf_outscal_apressure= 1. _d 0
346 heimbach 1.3
347 heimbach 1.1 c Check for the availability of the right calendar version.
348     if ( calendarversion .ne. usescalendarversion ) then
349     print*,' exf_readparms: You are not using the appropriate'
350     print*,' version of the calendar package.'
351     print*
352     print*,' You are using Calendar version: ', calendarversion
353     print*,' Please use Calendar version: ', usescalendarversion
354     stop ' stopped in exf_readparms.'
355     endif
356    
357     c Next, read the forcing data file.
358     call nml_filter( 'data.exf', scrunit1, myThid )
359     if (scrunit1 .eq. 0) then
360     stop 'exf_readparms: reading namelist failed'
361     end if
362     read( scrunit1, nml = exf_nml )
363     close( scrunit1 )
364    
365     c Complete the start date specifications for the forcing
366     c fields to get a complete calendar date array.
367    
368     c check for consistency
369    
370     if (.NOT.
371     & (exf_iprec .EQ. 32 .OR. exf_iprec .EQ. 64)
372     & ) then
373     stop 'stop in exf_readparms: value of exf_iprec not allowed'
374     else if (.NOT.
375     & (exf_yftype .EQ. 'RS' .OR.
376     & exf_yftype .EQ. 'RL')
377     & ) then
378     stop 'stop in exf_readparms: value of exf_yftype not allowed'
379     end if
380 dimitri 1.5
381 dimitri 1.6 #ifdef ALLOW_ATM_WIND
382 dimitri 1.13 call cal_FullDate ( uwindstartdate1 , uwindstartdate2,
383     & date_array ,mythid )
384     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
385     call cal_ToSeconds ( difftime, uwindstartdate ,mythid )
386     uwindstartdate = modelstart + uwindstartdate
387     call cal_FullDate ( vwindstartdate1 , vwindstartdate2,
388     & date_array ,mythid )
389     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
390     call cal_ToSeconds ( difftime, vwindstartdate ,mythid )
391     vwindstartdate = modelstart + vwindstartdate
392 dimitri 1.6 #else
393 dimitri 1.13 call cal_FullDate ( ustressstartdate1 , ustressstartdate2,
394     & date_array ,mythid )
395     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
396     call cal_ToSeconds ( difftime, ustressstartdate ,mythid )
397     ustressstartdate = modelstart + ustressstartdate
398     call cal_FullDate ( vstressstartdate1 , vstressstartdate2,
399     & date_array ,mythid )
400     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
401     call cal_ToSeconds ( difftime, vstressstartdate ,mythid )
402     vstressstartdate = modelstart + vstressstartdate
403 heimbach 1.3 #endif
404    
405 heimbach 1.1 #ifdef ALLOW_ATM_TEMP
406 dimitri 1.13 call cal_FullDate ( atempstartdate1 , atempstartdate2,
407     & date_array ,mythid )
408     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
409     call cal_ToSeconds ( difftime, atempstartdate ,mythid )
410     atempstartdate = modelstart + atempstartdate
411     call cal_FullDate ( aqhstartdate1 , aqhstartdate2,
412     & date_array ,mythid )
413     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
414     call cal_ToSeconds ( difftime, aqhstartdate ,mythid )
415     aqhstartdate = modelstart + aqhstartdate
416     call cal_FullDate ( lwfluxstartdate1 , lwfluxstartdate2,
417     & date_array ,mythid )
418     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
419     call cal_ToSeconds ( difftime, lwfluxstartdate ,mythid )
420     lwfluxstartdate = modelstart + lwfluxstartdate
421     call cal_FullDate ( precipstartdate1 , precipstartdate2,
422     & date_array ,mythid )
423     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
424     call cal_ToSeconds ( difftime, precipstartdate ,mythid )
425     precipstartdate = modelstart + precipstartdate
426 heimbach 1.1 #else
427 dimitri 1.13 call cal_FullDate ( hfluxstartdate1 , hfluxstartdate2,
428     & date_array ,mythid )
429     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
430     call cal_ToSeconds ( difftime, hfluxstartdate ,mythid )
431     hfluxstartdate = modelstart + hfluxstartdate
432     call cal_FullDate ( sfluxstartdate1 , sfluxstartdate2,
433     & date_array ,mythid )
434     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
435     call cal_ToSeconds ( difftime, sfluxstartdate ,mythid )
436     sfluxstartdate = modelstart + sfluxstartdate
437 heimbach 1.1 #endif
438    
439 dimitri 1.6 #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
440 dimitri 1.13 call cal_FullDate ( swfluxstartdate1 , swfluxstartdate2,
441     & date_array ,mythid )
442     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
443     call cal_ToSeconds ( difftime, swfluxstartdate ,mythid )
444     swfluxstartdate = modelstart + swfluxstartdate
445 heimbach 1.1 #endif
446    
447 dimitri 1.6 #ifdef EXF_READ_EVAP
448 dimitri 1.13 call cal_FullDate ( evapstartdate1 , evapstartdate2,
449     & date_array ,mythid )
450     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
451     call cal_ToSeconds ( difftime, evapstartdate ,mythid )
452     evapstartdate = modelstart + evapstartdate
453 heimbach 1.1 #endif
454    
455 dimitri 1.6 #ifdef ALLOW_RUNOFF
456 dimitri 1.13 call cal_FullDate ( runoffstartdate1 , runoffstartdate2,
457     & date_array ,mythid )
458     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
459     call cal_ToSeconds ( difftime, runoffstartdate ,mythid )
460     runoffstartdate = modelstart + runoffstartdate
461 heimbach 1.1 #endif
462    
463 dimitri 1.6 #ifdef ALLOW_DOWNWARD_RADIATION
464 dimitri 1.13 call cal_FullDate ( swdownstartdate1 , swdownstartdate2,
465     & date_array ,mythid )
466     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
467     call cal_ToSeconds ( difftime, swdownstartdate ,mythid )
468     swdownstartdate = modelstart + swdownstartdate
469     call cal_FullDate ( lwdownstartdate1 , lwdownstartdate2,
470     & date_array ,mythid )
471     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
472     call cal_ToSeconds ( difftime, lwdownstartdate ,mythid )
473     lwdownstartdate = modelstart + lwdownstartdate
474 heimbach 1.1 #endif
475    
476     #ifdef ALLOW_OBCS
477 heimbach 1.2 #ifdef ALLOW_OBCS_NORTH
478 dimitri 1.13 call cal_FullDate ( obcsNstartdate1 , obcsNstartdate2,
479     & date_array ,mythid )
480     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
481     call cal_ToSeconds ( difftime, obcsNstartdate ,mythid )
482     obcsNstartdate = modelstart + obcsNstartdate
483 heimbach 1.2 #endif
484     #ifdef ALLOW_OBCS_SOUTH
485 dimitri 1.13 call cal_FullDate ( obcsSstartdate1 , obcsSstartdate2,
486     & date_array ,mythid )
487     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
488     call cal_ToSeconds ( difftime, obcsSstartdate ,mythid )
489     obcsSstartdate = modelstart + obcsSstartdate
490 heimbach 1.2 #endif
491     #ifdef ALLOW_OBCS_EAST
492 dimitri 1.13 call cal_FullDate ( obcsEstartdate1 , obcsEstartdate2,
493     & date_array ,mythid )
494     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
495     call cal_ToSeconds ( difftime, obcsEstartdate ,mythid )
496     obcsEstartdate = modelstart + obcsEstartdate
497 heimbach 1.2 #endif
498     #ifdef ALLOW_OBCS_WEST
499 dimitri 1.13 call cal_FullDate ( obcsWstartdate1 , obcsWstartdate2,
500     & date_array ,mythid )
501     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
502     call cal_ToSeconds ( difftime, obcsWstartdate ,mythid )
503     obcsWstartdate = modelstart + obcsWstartdate
504 heimbach 1.3 #endif
505 dimitri 1.6 #endif /* ALLOW_OBCS */
506 heimbach 1.3
507     #ifdef ATMOSPHERIC_LOADING
508 dimitri 1.13 call cal_FullDate ( apressurestartdate1, apressurestartdate2,
509     & date_array ,mythid )
510     call cal_TimePassed( modelstartdate,date_array,difftime,mythid )
511     call cal_ToSeconds ( difftime, apressurestartdate ,mythid )
512     apressurestartdate = modelstart + apressurestartdate
513 heimbach 1.1 #endif
514    
515     _END_MASTER( mythid )
516    
517     _BARRIER
518    
519     c-- Summarize the External forcing's setup.
520     call exf_summary( mythid )
521    
522     c-- set climatology parameters
523     call exf_clim_readparms( mythid )
524    
525     c-- summarize climatologic forcing configuration
526     call exf_clim_summary( mythid )
527    
528     end

  ViewVC Help
Powered by ViewVC 1.1.22