/[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.10 - (hide annotations) (download)
Thu Aug 7 02:31:29 2003 UTC (20 years, 10 months ago) by dimitri
Branch: MAIN
CVS Tags: checkpoint51f_pre
Changes since 1.9: +2 -5 lines
o Added on-the-fly spatial interpolation capability
    "USE_EXF_INTERPOLATION" to pkg/exf.
  - This is a temporary Cartesian-grid hack until
    the super-duper ESMF coupler becomes available.
  - See verification/global_with_exf/README for usage example.
  - Removed obsolete EXFwindOnBgrid and SEAICEwindOnCgrid
    flags and modified pkg/seaice accordingly.
o Bug fix to pkg/ptracers, pkg/generic_advdiff/gad_calc_rhs.F,
    and pkg/kpp/kpp_transport_ptr.F for dealing with tracer
    non-local transport term.

1 dimitri 1.10 c $Header: /u/gcmpack/MITgcm/pkg/exf/exf_readparms.F,v 1.9 2003/08/04 22:53:42 dimitri 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 heimbach 1.8 & exf_inscal_hflux, exf_inscal_sflux,
101     & exf_inscal_ustress, exf_inscal_vstress,
102     & exf_inscal_uwind, exf_inscal_vwind,
103     & exf_inscal_evap, exf_inscal_atemp, exf_inscal_aqh,
104     & exf_inscal_sst, exf_inscal_sss,
105     & exf_inscal_swflux, exf_inscal_lwflux, exf_inscal_precip,
106     & exf_inscal_runoff, exf_inscal_apressure,
107     & exf_inscal_swdown, exf_inscal_lwdown,
108     & exf_outscal_hflux, exf_outscal_ustress, exf_outscal_vstress,
109     & exf_outscal_swflux, exf_outscal_sst,exf_outscal_sss,
110     & exf_outscal_sflux, exf_outscal_apressure,
111 heimbach 1.7 & hfluxconst,
112     & atempconst,
113     & aqhconst,
114     & sfluxconst,
115     & evapconst,
116     & precipconst,
117     & runoffconst,
118     & ustressconst,
119     & vstressconst,
120     & uwindconst,
121     & vwindconst,
122     & swfluxconst,
123     & lwfluxconst,
124     & swdownconst,
125     & lwdownconst,
126 dimitri 1.10 & apressureconst
127 dimitri 1.9 #ifdef USE_EXF_INTERPOLATION
128     & ,ustress_lon0, ustress_lon_inc,
129     & ustress_lat0, ustress_lat_inc,
130     & ustress_nlon, ustress_nlat,
131     & vstress_lon0, vstress_lon_inc,
132     & vstress_lat0, vstress_lat_inc,
133     & vstress_nlon, vstress_nlat,
134     & hflux_lon0, hflux_lon_inc,
135     & hflux_lat0, hflux_lat_inc,
136     & hflux_nlon, hflux_nlat,
137     & sflux_lon0, sflux_lon_inc,
138     & sflux_lat0, sflux_lat_inc,
139     & sflux_nlon, sflux_nlat,
140     & swflux_lon0, swflux_lon_inc,
141     & swflux_lat0, swflux_lat_inc,
142     & swflux_nlon, swflux_nlat,
143     & runoff_lon0, runoff_lon_inc,
144     & runoff_lat0, runoff_lat_inc,
145     & runoff_nlon, runoff_nlat,
146     & atemp_lon0, atemp_lon_inc,
147     & atemp_lat0, atemp_lat_inc,
148     & atemp_nlon, atemp_nlat,
149     & aqh_lon0, aqh_lon_inc,
150     & aqh_lat0, aqh_lat_inc,
151     & aqh_nlon, aqh_nlat,
152     & evap_lon0, evap_lon_inc,
153     & evap_lat0, evap_lat_inc,
154     & evap_nlon, evap_nlat,
155     & precip_lon0, precip_lon_inc,
156     & precip_lat0, precip_lat_inc,
157     & precip_nlon, precip_nlat,
158     & uwind_lon0, uwind_lon_inc,
159     & uwind_lat0, uwind_lat_inc,
160     & uwind_nlon, uwind_nlat,
161     & vwind_lon0, vwind_lon_inc,
162     & vwind_lat0, vwind_lat_inc,
163     & vwind_nlon, vwind_nlat,
164     & lwflux_lon0, lwflux_lon_inc,
165     & lwflux_lat0, lwflux_lat_inc,
166     & lwflux_nlon, lwflux_nlat,
167     & swdown_lon0, swdown_lon_inc,
168     & swdown_lat0, swdown_lat_inc,
169     & swdown_nlon, swdown_nlat,
170     & lwdown_lon0, lwdown_lon_inc,
171     & lwdown_lat0, lwdown_lat_inc,
172     & lwdown_nlon, lwdown_nlat,
173     & apressure_lon0,apressure_lon_inc,
174     & apressure_lat0,apressure_lat_inc,
175     & apressure_nlon,apressure_nlat
176     #endif
177 heimbach 1.1
178     _BEGIN_MASTER(mythid)
179    
180     c Set default values.
181    
182     c Calendar data.
183     hfluxstartdate1 = 0
184     hfluxstartdate2 = 0
185     hfluxperiod = 0.0 _d 0
186 heimbach 1.7 hfluxconst = 0.0 _d 0
187 heimbach 1.1
188     atempstartdate1 = 0
189     atempstartdate2 = 0
190     atempperiod = 0.0 _d 0
191 heimbach 1.7 atempconst = 0.0 _d 0
192 heimbach 1.1
193     aqhstartdate1 = 0
194     aqhstartdate2 = 0
195     aqhperiod = 0.0 _d 0
196 heimbach 1.7 aqhconst = 0.0 _d 0
197 heimbach 1.1
198     sfluxstartdate1 = 0
199     sfluxstartdate2 = 0
200     sfluxperiod = 0.0 _d 0
201 heimbach 1.7 sfluxconst = 0.0 _d 0
202 heimbach 1.1
203 dimitri 1.5 evapstartdate1 = 0
204     evapstartdate2 = 0
205     evapperiod = 0.0 _d 0
206 heimbach 1.7 evapconst = 0.0 _d 0
207 dimitri 1.5
208 heimbach 1.1 precipstartdate1 = 0
209     precipstartdate2 = 0
210     precipperiod = 0.0 _d 0
211 heimbach 1.7 precipconst = 0.0 _d 0
212 heimbach 1.1
213 heimbach 1.3 runoffstartdate1 = 0
214     runoffstartdate2 = 0
215     runoffperiod = 0.0 _d 0
216 heimbach 1.7 runoffconst = 0.0 _d 0
217 heimbach 1.3
218 heimbach 1.1 ustressstartdate1 = 0
219     ustressstartdate2 = 0
220     ustressperiod = 0.0 _d 0
221 heimbach 1.7 ustressconst = 0.0 _d 0
222 heimbach 1.1
223     vstressstartdate1 = 0
224     vstressstartdate2 = 0
225     vstressperiod = 0.0 _d 0
226 heimbach 1.7 vstressconst = 0.0 _d 0
227 heimbach 1.1
228     uwindstartdate1 = 0
229     uwindstartdate2 = 0
230     uwindperiod = 0.0 _d 0
231 heimbach 1.7 uwindconst = 0.0 _d 0
232 heimbach 1.1
233     vwindstartdate1 = 0
234     vwindstartdate2 = 0
235     vwindperiod = 0.0 _d 0
236 heimbach 1.7 vwindconst = 0.0 _d 0
237 heimbach 1.1
238     swfluxstartdate1 = 0
239     swfluxstartdate2 = 0
240     swfluxperiod = 0.0 _d 0
241 heimbach 1.7 swfluxconst = 0.0 _d 0
242 heimbach 1.1
243     lwfluxstartdate1 = 0
244     lwfluxstartdate2 = 0
245     lwfluxperiod = 0.0 _d 0
246 heimbach 1.7 lwfluxconst = 0.0 _d 0
247 heimbach 1.1
248 dimitri 1.6 swdownstartdate1 = 0
249     swdownstartdate2 = 0
250     swdownperiod = 0.0 _d 0
251 heimbach 1.7 swdownconst = 0.0 _d 0
252 dimitri 1.6
253     lwdownstartdate1 = 0
254     lwdownstartdate2 = 0
255     lwdownperiod = 0.0 _d 0
256 heimbach 1.7 lwdownconst = 0.0 _d 0
257 dimitri 1.6
258 heimbach 1.2 obcsNstartdate1 = 0
259     obcsNstartdate2 = 0
260     obcsNperiod = 0.0 _d 0
261    
262     obcsSstartdate1 = 0
263     obcsSstartdate2 = 0
264     obcsSperiod = 0.0 _d 0
265    
266     obcsEstartdate1 = 0
267     obcsEstartdate2 = 0
268     obcsEperiod = 0.0 _d 0
269    
270     obcsWstartdate1 = 0
271     obcsWstartdate2 = 0
272     obcsWperiod = 0.0 _d 0
273 heimbach 1.1
274 heimbach 1.3 apressurestartdate1 = 0
275     apressurestartdate2 = 0
276     apressureperiod = 0.0 _d 0
277 heimbach 1.7 apressureconst = 0.0 _d 0
278 cheisey 1.4
279     repeatPeriod = 0.0 _d 0
280    
281 heimbach 1.1 c Data files.
282     hfluxfile = ' '
283     atempfile = ' '
284     aqhfile = ' '
285 dimitri 1.5 evapfile = ' '
286 heimbach 1.1 precipfile = ' '
287     sfluxfile = ' '
288 heimbach 1.3 runofffile = ' '
289 heimbach 1.1 ustressfile = ' '
290     vstressfile = ' '
291     uwindfile = ' '
292     vwindfile = ' '
293     swfluxfile = ' '
294     lwfluxfile = ' '
295 dimitri 1.6 swdownfile = ' '
296     lwdownfile = ' '
297 heimbach 1.3 apressurefile = ' '
298 heimbach 1.1
299     c Initialise the date arrays.
300     do i = 1,4
301     hfluxstartdate(i) = 0
302     atempstartdate(i) = 0
303     aqhstartdate(i) = 0
304 dimitri 1.5 evapstartdate(i) = 0
305 heimbach 1.1 precipstartdate(i) = 0
306     sfluxstartdate(i) = 0
307 heimbach 1.3 runoffstartdate(i) = 0
308 heimbach 1.1 ustressstartdate(i) = 0
309     vstressstartdate(i) = 0
310     uwindstartdate(i) = 0
311     vwindstartdate(i) = 0
312     swfluxstartdate(i) = 0
313     lwfluxstartdate(i) = 0
314 dimitri 1.6 swdownstartdate(i) = 0
315     lwdownstartdate(i) = 0
316 heimbach 1.2 obcsNstartdate(i) = 0
317     obcsSstartdate(i) = 0
318     obcsEstartdate(i) = 0
319     obcsWstartdate(i) = 0
320 heimbach 1.3 apressurestartdate(i)= 0
321 heimbach 1.1 enddo
322    
323     c Initialise file type and field precision
324     exf_iprec = 32
325     exf_yftype = 'RL'
326    
327 dimitri 1.6 c Input scaling factors.
328 heimbach 1.8 exf_inscal_hflux = 1. _d 0
329     exf_inscal_sflux = 1. _d 0
330     exf_inscal_ustress = 1. _d 0
331     exf_inscal_vstress = 1. _d 0
332     exf_inscal_uwind = 1. _d 0
333     exf_inscal_vwind = 1. _d 0
334     exf_inscal_swflux = 1. _d 0
335     exf_inscal_lwflux = 1. _d 0
336     exf_inscal_precip = 1. _d 0
337 dimitri 1.6 exf_inscal_sst = 1. _d 0
338     exf_inscal_sss = 1. _d 0
339 heimbach 1.8 exf_inscal_atemp = 1. _d 0
340     exf_inscal_aqh = 1. _d 0
341     exf_inscal_evap = 1. _d 0
342 dimitri 1.6 exf_inscal_apressure = 1. _d 0
343     cds convert runoff from m/yr to m/s and change sign.
344     exf_inscal_runoff = -1.0/(86400.*365.0)
345 heimbach 1.8 exf_inscal_swdown = 1. _d 0
346     exf_inscal_lwdown = 1. _d 0
347 dimitri 1.6
348     c Output scaling factors.
349 heimbach 1.8 exf_outscal_hflux = 1. _d 0
350     exf_outscal_sflux = 1. _d 0
351     exf_outscal_ustress = 1. _d 0
352     exf_outscal_vstress = 1. _d 0
353     exf_outscal_swflux = 1. _d 0
354 dimitri 1.6 exf_outscal_sst = 1. _d 0
355     exf_outscal_sss = 1. _d 0
356     exf_outscal_apressure= 1. _d 0
357 heimbach 1.3
358 heimbach 1.1 c Check for the availability of the right calendar version.
359     if ( calendarversion .ne. usescalendarversion ) then
360     print*,' exf_readparms: You are not using the appropriate'
361     print*,' version of the calendar package.'
362     print*
363     print*,' You are using Calendar version: ', calendarversion
364     print*,' Please use Calendar version: ', usescalendarversion
365     stop ' stopped in exf_readparms.'
366     endif
367    
368     c Next, read the forcing data file.
369     call nml_filter( 'data.exf', scrunit1, myThid )
370     if (scrunit1 .eq. 0) then
371     stop 'exf_readparms: reading namelist failed'
372     end if
373     read( scrunit1, nml = exf_nml )
374     close( scrunit1 )
375    
376     c Complete the start date specifications for the forcing
377     c fields to get a complete calendar date array.
378    
379     c check for consistency
380    
381     if (.NOT.
382     & (exf_iprec .EQ. 32 .OR. exf_iprec .EQ. 64)
383     & ) then
384     stop 'stop in exf_readparms: value of exf_iprec not allowed'
385     else if (.NOT.
386     & (exf_yftype .EQ. 'RS' .OR.
387     & exf_yftype .EQ. 'RL')
388     & ) then
389     stop 'stop in exf_readparms: value of exf_yftype not allowed'
390     end if
391 dimitri 1.5
392 dimitri 1.6 #ifdef ALLOW_ATM_WIND
393     call cal_FullDate( uwindstartdate1, uwindstartdate2,
394     & uwindstartdate , mythid )
395     call cal_FullDate( vwindstartdate1, vwindstartdate2,
396     & vwindstartdate , mythid )
397     #else
398     call cal_FullDate( ustressstartdate1, ustressstartdate2,
399     & ustressstartdate , mythid )
400     call cal_FullDate( vstressstartdate1, vstressstartdate2,
401     & vstressstartdate , mythid )
402 heimbach 1.3 #endif
403    
404 heimbach 1.1 #ifdef ALLOW_ATM_TEMP
405 dimitri 1.6 call cal_FullDate( atempstartdate1, atempstartdate2,
406     & atempstartdate , mythid )
407     call cal_FullDate( aqhstartdate1, aqhstartdate2,
408     & aqhstartdate , mythid )
409     call cal_FullDate( lwfluxstartdate1, lwfluxstartdate2,
410     & lwfluxstartdate , mythid )
411     call cal_FullDate( precipstartdate1, precipstartdate2,
412     & precipstartdate , mythid )
413 heimbach 1.1 #else
414 dimitri 1.6 call cal_FullDate( hfluxstartdate1, hfluxstartdate2,
415     & hfluxstartdate , mythid )
416     call cal_FullDate( sfluxstartdate1, sfluxstartdate2,
417     & sfluxstartdate , mythid )
418 heimbach 1.1 #endif
419    
420 dimitri 1.6 #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
421     call cal_FullDate( swfluxstartdate1, swfluxstartdate2,
422     & swfluxstartdate , mythid )
423 heimbach 1.1 #endif
424    
425 dimitri 1.6 #ifdef EXF_READ_EVAP
426     call cal_FullDate( evapstartdate1, evapstartdate2,
427     & evapstartdate , mythid )
428 heimbach 1.1 #endif
429    
430 dimitri 1.6 #ifdef ALLOW_RUNOFF
431     call cal_FullDate( runoffstartdate1, runoffstartdate2,
432     & runoffstartdate , mythid )
433 heimbach 1.1 #endif
434    
435 dimitri 1.6 #ifdef ALLOW_DOWNWARD_RADIATION
436     call cal_FullDate( swdownstartdate1, swdownstartdate2,
437     & swdownstartdate , mythid )
438     call cal_FullDate( lwdownstartdate1, lwdownstartdate2,
439     & lwdownstartdate , mythid )
440 heimbach 1.1 #endif
441    
442     #ifdef ALLOW_OBCS
443 heimbach 1.2 #ifdef ALLOW_OBCS_NORTH
444 dimitri 1.6 call cal_FullDate( obcsNstartdate1, obcsNstartdate2,
445     & obcsNstartdate , mythid )
446 heimbach 1.2 #endif
447     #ifdef ALLOW_OBCS_SOUTH
448 dimitri 1.6 call cal_FullDate( obcsSstartdate1, obcsSstartdate2,
449     & obcsSstartdate , mythid )
450 heimbach 1.2 #endif
451     #ifdef ALLOW_OBCS_EAST
452 dimitri 1.6 call cal_FullDate( obcsEstartdate1, obcsEstartdate2,
453     & obcsEstartdate , mythid )
454 heimbach 1.2 #endif
455     #ifdef ALLOW_OBCS_WEST
456 dimitri 1.6 call cal_FullDate( obcsWstartdate1, obcsWstartdate2,
457     & obcsWstartdate , mythid )
458 heimbach 1.3 #endif
459 dimitri 1.6 #endif /* ALLOW_OBCS */
460 heimbach 1.3
461     #ifdef ATMOSPHERIC_LOADING
462 dimitri 1.6 call cal_FullDate(apressurestartdate1,apressurestartdate2,
463     & apressurestartdate , mythid )
464 heimbach 1.1 #endif
465    
466     _END_MASTER( mythid )
467    
468     _BARRIER
469    
470     c-- Summarize the External forcing's setup.
471     call exf_summary( mythid )
472    
473     c-- set climatology parameters
474     call exf_clim_readparms( mythid )
475    
476     c-- summarize climatologic forcing configuration
477     call exf_clim_summary( mythid )
478    
479     end

  ViewVC Help
Powered by ViewVC 1.1.22