/[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.7 - (hide annotations) (download)
Thu Mar 6 00:47:33 2003 UTC (21 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint50c_post, checkpoint50c_pre, checkpoint50, checkpoint50d_post, checkpoint50b_pre, checkpoint50a_post, checkpoint50f_pre, checkpoint50e_pre, checkpoint50e_post, checkpoint50d_pre, checkpoint49, checkpoint50b_post
Changes since 1.6: +34 -2 lines
merged from ecco-branch:
o exf:
  - Enable initialisation of forcing fields to constant
    (runtime) values.
  - in exf_getffields.F
    Reduce i-/j-loop to interior domain, discarding overlaps.
    That also fixes wrong TAF-key computations for key_1, key_2
    with bulf formulae.
  - exf_init.F modify #ifdef for exf_init_evap
  - exf_getffieldrec.F, ctrl_getrec.F
    The following INT-usages are not safe:
      fldsecs  = int(fldsecs/fldperiod)*fldperiod
      fldcount = int(fldsecs/fldperiod) + 1
    and were modified.

1 heimbach 1.7 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_readparms.F,v 1.1.6.6 2003/03/04 00:17:40 heimbach Exp $
2 heimbach 1.1
3     #include "EXF_CPPOPTIONS.h"
4 heimbach 1.3 #ifdef ALLOW_OBCS
5     # include "OBCS_OPTIONS.h"
6     #endif
7 heimbach 1.1
8 heimbach 1.3 subroutine exf_readparms( mythid )
9 heimbach 1.1
10     c ==================================================================
11     c SUBROUTINE exf_readparms
12     c ==================================================================
13     c
14     c o This routine initialises the package that calculates external
15     c forcing fields for a given timestep of the MITgcmUV. Parameters
16     c for this package are set in "data.externalforcing". Some additional
17 heimbach 1.2 c precompiler switches have to be specified in "EXF_CPPOPTIONS.h".
18 heimbach 1.1 c
19     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
20     c
21     c changed: Christian Eckert eckert@mit.edu 11-Jan-2000
22     c - Restructured the code in order to create a package
23     c for the MITgcmUV.
24     c Christian Eckert eckert@mit.edu 12-Feb-2000
25     c - Changed Routine names (package prefix: exf_)
26 heimbach 1.2 c changed: Patrick Heimbach, heimbach@mit.edu 04-May-2000
27 heimbach 1.1 c - changed the handling of precip and sflux with respect
28     c to CPP options ALLOW_BULKFORMULAE and ALLOW_ATM_TEMP
29     c changed: Ralf.Giering@FastOpt.de 25-Mai-20000
30 heimbach 1.2 c - moved relaxation and climatology to extra routines
31 heimbach 1.1 c Patrick Heimbach, heimbach@mit.edu 04-May-2000
32     c - added obcs parameters
33 heimbach 1.2 c changed: Virginie Thierry, vthierry@ucsd.edu 04-June-2001
34     c - added new obcs parameters (for each boundaries)
35 heimbach 1.3 c included runoff D. Stammer, Nov. 25, 2001
36     c included pressure forcing. heimbach@mit.edu 05-Nov-2002
37 dimitri 1.5 c added "repeatPeriod" for cycling of forcing datasets 19-Dec-2002
38 dimitri 1.6 c mods for pkg/seaice: menemenlis@jpl.nasa.gov 20-Dec-2002
39 heimbach 1.1 c
40     c ==================================================================
41     c SUBROUTINE exf_readparms
42     c ==================================================================
43    
44     implicit none
45    
46     c == global variables ==
47    
48     #include "EEPARAMS.h"
49     #include "SIZE.h"
50     #include "cal.h"
51     #include "exf.h"
52     #include "exf_param.h"
53     #include "exf_constants.h"
54    
55     c == routine arguments ==
56    
57     integer mythid
58    
59     c == local variables ==
60    
61     integer i
62    
63     c == external ==
64    
65     integer ilnblnk
66     external ilnblnk
67    
68     c == end of interface ==
69    
70     c Surface flux data.
71     namelist /exf_nml/
72 cheisey 1.4 & repeatPeriod,
73 heimbach 1.1 & hfluxstartdate1, hfluxstartdate2, hfluxperiod,
74     & atempstartdate1, atempstartdate2, atempperiod,
75     & aqhstartdate1, aqhstartdate2, aqhperiod,
76     & sfluxstartdate1, sfluxstartdate2, sfluxperiod,
77 dimitri 1.5 & evapstartdate1, evapstartdate2, evapperiod,
78 heimbach 1.1 & precipstartdate1, precipstartdate2, precipperiod,
79 heimbach 1.3 & runoffstartdate1, runoffstartdate2, runoffperiod,
80 heimbach 1.1 & ustressstartdate1, ustressstartdate2, ustressperiod,
81     & vstressstartdate1, vstressstartdate2, vstressperiod,
82     & uwindstartdate1, uwindstartdate2, uwindperiod,
83     & vwindstartdate1, vwindstartdate2, vwindperiod,
84     & swfluxstartdate1, swfluxstartdate2, swfluxperiod,
85     & lwfluxstartdate1, lwfluxstartdate2, lwfluxperiod,
86 dimitri 1.6 & swdownstartdate1, swdownstartdate2, swdownperiod,
87     & lwdownstartdate1, lwdownstartdate2, lwdownperiod,
88 heimbach 1.2 & obcsNstartdate1, obcsNstartdate2, obcsNperiod,
89     & obcsSstartdate1, obcsSstartdate2, obcsSperiod,
90     & obcsEstartdate1, obcsEstartdate2, obcsEperiod,
91     & obcsWstartdate1, obcsWstartdate2, obcsWperiod,
92 heimbach 1.3 &apressurestartdate1,apressurestartdate2,apressureperiod,
93 heimbach 1.1 & hfluxfile, atempfile, aqhfile,
94 heimbach 1.3 & sfluxfile, precipfile, runofffile,
95 dimitri 1.5 & ustressfile, vstressfile, evapfile,
96 heimbach 1.3 & uwindfile, vwindfile,
97     & swfluxfile, lwfluxfile, apressurefile,
98 dimitri 1.6 & swdownfile, lwdownfile,
99 heimbach 1.3 & exf_iprec, exf_yftype,
100 dimitri 1.6 & exf_inscal_hfl, exf_inscal_ust, exf_inscal_vst,
101     & exf_inscal_swf, exf_inscal_sst, exf_inscal_sss,
102     & exf_inscal_sfl, exf_inscal_runoff,exf_inscal_apressure,
103     & exf_outscal_hfl, exf_outscal_ust,exf_outscal_vst,
104     & exf_outscal_swf, exf_outscal_sst,exf_outscal_sss,
105     & exf_outscal_sfl, exf_outscal_apressure,
106 heimbach 1.7 & hfluxconst,
107     & atempconst,
108     & aqhconst,
109     & sfluxconst,
110     & evapconst,
111     & precipconst,
112     & runoffconst,
113     & ustressconst,
114     & vstressconst,
115     & uwindconst,
116     & vwindconst,
117     & swfluxconst,
118     & lwfluxconst,
119     & swdownconst,
120     & lwdownconst,
121     & apressureconst,
122     & EXFwindOnBgrid
123 heimbach 1.1
124     _BEGIN_MASTER(mythid)
125    
126     c Set default values.
127    
128     c Calendar data.
129     hfluxstartdate1 = 0
130     hfluxstartdate2 = 0
131     hfluxperiod = 0.0 _d 0
132 heimbach 1.7 hfluxconst = 0.0 _d 0
133 heimbach 1.1
134     atempstartdate1 = 0
135     atempstartdate2 = 0
136     atempperiod = 0.0 _d 0
137 heimbach 1.7 atempconst = 0.0 _d 0
138 heimbach 1.1
139     aqhstartdate1 = 0
140     aqhstartdate2 = 0
141     aqhperiod = 0.0 _d 0
142 heimbach 1.7 aqhconst = 0.0 _d 0
143 heimbach 1.1
144     sfluxstartdate1 = 0
145     sfluxstartdate2 = 0
146     sfluxperiod = 0.0 _d 0
147 heimbach 1.7 sfluxconst = 0.0 _d 0
148 heimbach 1.1
149 dimitri 1.5 evapstartdate1 = 0
150     evapstartdate2 = 0
151     evapperiod = 0.0 _d 0
152 heimbach 1.7 evapconst = 0.0 _d 0
153 dimitri 1.5
154 heimbach 1.1 precipstartdate1 = 0
155     precipstartdate2 = 0
156     precipperiod = 0.0 _d 0
157 heimbach 1.7 precipconst = 0.0 _d 0
158 heimbach 1.1
159 heimbach 1.3 runoffstartdate1 = 0
160     runoffstartdate2 = 0
161     runoffperiod = 0.0 _d 0
162 heimbach 1.7 runoffconst = 0.0 _d 0
163 heimbach 1.3
164 heimbach 1.1 ustressstartdate1 = 0
165     ustressstartdate2 = 0
166     ustressperiod = 0.0 _d 0
167 heimbach 1.7 ustressconst = 0.0 _d 0
168 heimbach 1.1
169     vstressstartdate1 = 0
170     vstressstartdate2 = 0
171     vstressperiod = 0.0 _d 0
172 heimbach 1.7 vstressconst = 0.0 _d 0
173 heimbach 1.1
174     uwindstartdate1 = 0
175     uwindstartdate2 = 0
176     uwindperiod = 0.0 _d 0
177 heimbach 1.7 uwindconst = 0.0 _d 0
178 heimbach 1.1
179     vwindstartdate1 = 0
180     vwindstartdate2 = 0
181     vwindperiod = 0.0 _d 0
182 heimbach 1.7 vwindconst = 0.0 _d 0
183 heimbach 1.1
184     swfluxstartdate1 = 0
185     swfluxstartdate2 = 0
186     swfluxperiod = 0.0 _d 0
187 heimbach 1.7 swfluxconst = 0.0 _d 0
188 heimbach 1.1
189     lwfluxstartdate1 = 0
190     lwfluxstartdate2 = 0
191     lwfluxperiod = 0.0 _d 0
192 heimbach 1.7 lwfluxconst = 0.0 _d 0
193 heimbach 1.1
194 dimitri 1.6 swdownstartdate1 = 0
195     swdownstartdate2 = 0
196     swdownperiod = 0.0 _d 0
197 heimbach 1.7 swdownconst = 0.0 _d 0
198 dimitri 1.6
199     lwdownstartdate1 = 0
200     lwdownstartdate2 = 0
201     lwdownperiod = 0.0 _d 0
202 heimbach 1.7 lwdownconst = 0.0 _d 0
203 dimitri 1.6
204 heimbach 1.2 obcsNstartdate1 = 0
205     obcsNstartdate2 = 0
206     obcsNperiod = 0.0 _d 0
207    
208     obcsSstartdate1 = 0
209     obcsSstartdate2 = 0
210     obcsSperiod = 0.0 _d 0
211    
212     obcsEstartdate1 = 0
213     obcsEstartdate2 = 0
214     obcsEperiod = 0.0 _d 0
215    
216     obcsWstartdate1 = 0
217     obcsWstartdate2 = 0
218     obcsWperiod = 0.0 _d 0
219 heimbach 1.1
220 heimbach 1.3 apressurestartdate1 = 0
221     apressurestartdate2 = 0
222     apressureperiod = 0.0 _d 0
223 heimbach 1.7 apressureconst = 0.0 _d 0
224 cheisey 1.4
225     repeatPeriod = 0.0 _d 0
226    
227 heimbach 1.1 c Data files.
228     hfluxfile = ' '
229     atempfile = ' '
230     aqhfile = ' '
231 dimitri 1.5 evapfile = ' '
232 heimbach 1.1 precipfile = ' '
233     sfluxfile = ' '
234 heimbach 1.3 runofffile = ' '
235 heimbach 1.1 ustressfile = ' '
236     vstressfile = ' '
237     uwindfile = ' '
238     vwindfile = ' '
239     swfluxfile = ' '
240     lwfluxfile = ' '
241 dimitri 1.6 swdownfile = ' '
242     lwdownfile = ' '
243 heimbach 1.3 apressurefile = ' '
244 heimbach 1.1
245     c Initialise the date arrays.
246     do i = 1,4
247     hfluxstartdate(i) = 0
248     atempstartdate(i) = 0
249     aqhstartdate(i) = 0
250 dimitri 1.5 evapstartdate(i) = 0
251 heimbach 1.1 precipstartdate(i) = 0
252     sfluxstartdate(i) = 0
253 heimbach 1.3 runoffstartdate(i) = 0
254 heimbach 1.1 ustressstartdate(i) = 0
255     vstressstartdate(i) = 0
256     uwindstartdate(i) = 0
257     vwindstartdate(i) = 0
258     swfluxstartdate(i) = 0
259     lwfluxstartdate(i) = 0
260 dimitri 1.6 swdownstartdate(i) = 0
261     lwdownstartdate(i) = 0
262 heimbach 1.2 obcsNstartdate(i) = 0
263     obcsSstartdate(i) = 0
264     obcsEstartdate(i) = 0
265     obcsWstartdate(i) = 0
266 heimbach 1.3 apressurestartdate(i)= 0
267 heimbach 1.1 enddo
268    
269     c Initialise file type and field precision
270     exf_iprec = 32
271     exf_yftype = 'RL'
272    
273 dimitri 1.6 c Input scaling factors.
274     exf_inscal_hfl = 1. _d 0
275     exf_inscal_ust = 1. _d 0
276     exf_inscal_vst = 1. _d 0
277     exf_inscal_swf = 1. _d 0
278     exf_inscal_sst = 1. _d 0
279     exf_inscal_sss = 1. _d 0
280     exf_inscal_apressure = 1. _d 0
281     exf_inscal_sfl = 1. _d 0
282     cds convert runoff from m/yr to m/s and change sign.
283     exf_inscal_runoff = -1.0/(86400.*365.0)
284    
285     c Output scaling factors.
286     exf_outscal_hfl = 1. _d 0
287     exf_outscal_ust = 1. _d 0
288     exf_outscal_vst = 1. _d 0
289     exf_outscal_swf = 1. _d 0
290     exf_outscal_sst = 1. _d 0
291     exf_outscal_sss = 1. _d 0
292     exf_outscal_apressure= 1. _d 0
293     exf_outscal_sfl = 1. _d 0
294     c
295     EXFwindOnBgrid = .FALSE.
296 heimbach 1.3
297 heimbach 1.1 c Check for the availability of the right calendar version.
298     if ( calendarversion .ne. usescalendarversion ) then
299     print*,' exf_readparms: You are not using the appropriate'
300     print*,' version of the calendar package.'
301     print*
302     print*,' You are using Calendar version: ', calendarversion
303     print*,' Please use Calendar version: ', usescalendarversion
304     stop ' stopped in exf_readparms.'
305     endif
306    
307     c Next, read the forcing data file.
308     call nml_filter( 'data.exf', scrunit1, myThid )
309     if (scrunit1 .eq. 0) then
310     stop 'exf_readparms: reading namelist failed'
311     end if
312     read( scrunit1, nml = exf_nml )
313     close( scrunit1 )
314    
315     c Complete the start date specifications for the forcing
316     c fields to get a complete calendar date array.
317    
318     c check for consistency
319    
320     if (.NOT.
321     & (exf_iprec .EQ. 32 .OR. exf_iprec .EQ. 64)
322     & ) then
323     stop 'stop in exf_readparms: value of exf_iprec not allowed'
324     else if (.NOT.
325     & (exf_yftype .EQ. 'RS' .OR.
326     & exf_yftype .EQ. 'RL')
327     & ) then
328     stop 'stop in exf_readparms: value of exf_yftype not allowed'
329     end if
330 dimitri 1.5
331 dimitri 1.6 #ifdef ALLOW_ATM_WIND
332     call cal_FullDate( uwindstartdate1, uwindstartdate2,
333     & uwindstartdate , mythid )
334     call cal_FullDate( vwindstartdate1, vwindstartdate2,
335     & vwindstartdate , mythid )
336     #else
337     call cal_FullDate( ustressstartdate1, ustressstartdate2,
338     & ustressstartdate , mythid )
339     call cal_FullDate( vstressstartdate1, vstressstartdate2,
340     & vstressstartdate , mythid )
341 heimbach 1.3 #endif
342    
343 heimbach 1.1 #ifdef ALLOW_ATM_TEMP
344 dimitri 1.6 call cal_FullDate( atempstartdate1, atempstartdate2,
345     & atempstartdate , mythid )
346     call cal_FullDate( aqhstartdate1, aqhstartdate2,
347     & aqhstartdate , mythid )
348     call cal_FullDate( lwfluxstartdate1, lwfluxstartdate2,
349     & lwfluxstartdate , mythid )
350     call cal_FullDate( precipstartdate1, precipstartdate2,
351     & precipstartdate , mythid )
352 heimbach 1.1 #else
353 dimitri 1.6 call cal_FullDate( hfluxstartdate1, hfluxstartdate2,
354     & hfluxstartdate , mythid )
355     call cal_FullDate( sfluxstartdate1, sfluxstartdate2,
356     & sfluxstartdate , mythid )
357 heimbach 1.1 #endif
358    
359 dimitri 1.6 #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
360     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
361     & swfluxstartdate , mythid )
362 heimbach 1.1 #endif
363    
364 dimitri 1.6 #ifdef EXF_READ_EVAP
365     call cal_FullDate( evapstartdate1, evapstartdate2,
366     & evapstartdate , mythid )
367 heimbach 1.1 #endif
368    
369 dimitri 1.6 #ifdef ALLOW_RUNOFF
370     call cal_FullDate( runoffstartdate1, runoffstartdate2,
371     & runoffstartdate , mythid )
372 heimbach 1.1 #endif
373    
374 dimitri 1.6 #ifdef ALLOW_DOWNWARD_RADIATION
375     call cal_FullDate( swdownstartdate1, swdownstartdate2,
376     & swdownstartdate , mythid )
377     call cal_FullDate( lwdownstartdate1, lwdownstartdate2,
378     & lwdownstartdate , mythid )
379 heimbach 1.1 #endif
380    
381     #ifdef ALLOW_OBCS
382 heimbach 1.2 #ifdef ALLOW_OBCS_NORTH
383 dimitri 1.6 call cal_FullDate( obcsNstartdate1, obcsNstartdate2,
384     & obcsNstartdate , mythid )
385 heimbach 1.2 #endif
386     #ifdef ALLOW_OBCS_SOUTH
387 dimitri 1.6 call cal_FullDate( obcsSstartdate1, obcsSstartdate2,
388     & obcsSstartdate , mythid )
389 heimbach 1.2 #endif
390     #ifdef ALLOW_OBCS_EAST
391 dimitri 1.6 call cal_FullDate( obcsEstartdate1, obcsEstartdate2,
392     & obcsEstartdate , mythid )
393 heimbach 1.2 #endif
394     #ifdef ALLOW_OBCS_WEST
395 dimitri 1.6 call cal_FullDate( obcsWstartdate1, obcsWstartdate2,
396     & obcsWstartdate , mythid )
397 heimbach 1.3 #endif
398 dimitri 1.6 #endif /* ALLOW_OBCS */
399 heimbach 1.3
400     #ifdef ATMOSPHERIC_LOADING
401 dimitri 1.6 call cal_FullDate(apressurestartdate1,apressurestartdate2,
402     & apressurestartdate , mythid )
403 heimbach 1.1 #endif
404    
405     _END_MASTER( mythid )
406    
407     _BARRIER
408    
409     c-- Summarize the External forcing's setup.
410     call exf_summary( mythid )
411    
412     c-- set climatology parameters
413     call exf_clim_readparms( mythid )
414    
415     c-- summarize climatologic forcing configuration
416     call exf_clim_summary( mythid )
417    
418     end

  ViewVC Help
Powered by ViewVC 1.1.22