/[MITgcm]/MITgcm_contrib/ecco_darwin/v3_cs510_Brix/code/exf_summary.F
ViewVC logotype

Annotation of /MITgcm_contrib/ecco_darwin/v3_cs510_Brix/code/exf_summary.F

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


Revision 1.1 - (hide annotations) (download)
Tue Nov 28 19:50:42 2017 UTC (7 years, 8 months ago) by dimitri
Branch: MAIN
CVS Tags: HEAD
Holger Brix's ECCO-Darwin version 3 with circa-2011 MITgcm

1 dimitri 1.1 C $Header: /u/gcmpack/MITgcm/pkg/exf/exf_summary.F,v 1.24 2010/11/23 18:55:54 jmc Exp $
2     C $Name: $
3    
4     #include "EXF_OPTIONS.h"
5    
6    
7     SUBROUTINE EXF_SUMMARY( myThid )
8    
9     c ==================================================================
10     c SUBROUTINE exf_summary
11     c ==================================================================
12     c
13     c o List all the settings of the external forcing.
14     c
15     c started: Christian Eckert eckert@mit.edu 11-Jan-1999
16     c
17     c changed: Christian Eckert eckert@mit.edu 12-Feb-2000
18     c - changed routine names (package prefix: exf_)
19     c
20     c changed: Patrick Heimbach heimbach@mit.edu 04-May-2000
21     c - changed the handling of precip and sflux with respect
22     c to CPP options ALLOW_BULKFORMULAE and ALLOW_ATM_TEMP
23     c
24     c changed: Dimitris Menemenlis menemenlis@jpl.nasa.gov 20-Dec-2002
25     c - modifications for using pkg/exf with pkg/seaice
26     c
27     c ==================================================================
28     c SUBROUTINE exf_summary
29     c ==================================================================
30    
31     implicit none
32    
33     C == global variables ==
34    
35     #include "EEPARAMS.h"
36     #include "SIZE.h"
37     #include "cal.h"
38     #include "EXF_CONSTANTS.h"
39     #include "EXF_PARAM.h"
40    
41     C == routine arguments ==
42    
43     C myThid - thread number for this instance of the routine.
44    
45     integer myThid
46    
47     C == local variables ==
48    
49     integer il
50    
51     character*(max_len_mbuf) msgbuf
52    
53     C == external ==
54    
55     integer ilnblnk
56     external ilnblnk
57    
58     C == end of interface ==
59    
60     _BEGIN_MASTER( myThid )
61    
62     write(msgbuf,'(a)') ' '
63     call print_message( msgbuf, standardmessageunit,
64     & SQUEEZE_RIGHT , mythid)
65     write(msgbuf,'(a)')
66     &'// ======================================================='
67     call print_message( msgbuf, standardmessageunit,
68     & SQUEEZE_RIGHT , mythid)
69     write(msgbuf,'(a)')
70     &'// External forcing configuration >>> START <<<'
71     call print_message( msgbuf, standardmessageunit,
72     & SQUEEZE_RIGHT , mythid)
73     write(msgbuf,'(a)')
74     &'// ======================================================='
75     call print_message( msgbuf, standardmessageunit,
76     & SQUEEZE_RIGHT , mythid)
77     write(msgbuf,'(a)') ' '
78     call print_message( msgbuf, standardmessageunit,
79     & SQUEEZE_RIGHT , mythid)
80    
81     C-- Print general parameters:
82     WRITE(msgBuf,'(A)') ' EXF general parameters:'
83     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
84     & SQUEEZE_RIGHT , myThid )
85     WRITE(msgBuf,'(A)') ' '
86     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
87     & SQUEEZE_RIGHT , myThid )
88     CALL WRITE_0D_C( exf_yftype, 0, INDEX_NONE, 'exf_yftype = ',
89     & ' /* ? */')
90     CALL WRITE_0D_I( exf_iprec, INDEX_NONE, 'exf_iprec =',
91     & ' /* exf file precision */')
92     CALL WRITE_0D_L( useExfYearlyFields, INDEX_NONE,
93     & 'useExfYearlyFields =',
94     & ' /* add extension _YEAR to input file names */')
95     CALL WRITE_0D_L( twoDigitYear, INDEX_NONE, 'twoDigitYear =',
96     & ' /* use 2-digit year extension */')
97     CALL WRITE_0D_L( exf_verbose, INDEX_NONE, 'exf_verbose =',
98     & ' /* print more messages to STDOUT */')
99     CALL WRITE_0D_L( useExfCheckRange, INDEX_NONE,
100     & 'useExfCheckRange =', ' /* check for fields range */')
101     CALL WRITE_0D_RL( exf_monFreq, INDEX_NONE, 'exf_monFreq =',
102     & ' /* EXF monitor frequency [ s ] */')
103     CALL WRITE_0D_RL( repeatPeriod, INDEX_NONE, 'repeatPeriod =',
104     & ' /* period for cycling forcing dataset [ s ] */')
105     CALL WRITE_0D_RL( climtempfreeze, INDEX_NONE,'climTempFreeze=',
106     & ' /* Minimum climatological temperature [deg.C] */')
107     CALL WRITE_0D_RL( windStressMax, INDEX_NONE,'windStressMax =',
108     & ' /* Maximum absolute windstress [ Pa ] */')
109     CALL WRITE_0D_L( stressIsOnCgrid,INDEX_NONE,'stressIsOnCgrid =',
110     & ' /* set u,v_stress on Arakawa C-grid */')
111     CALL WRITE_0D_RL( cen2kel, INDEX_NONE, 'cen2kel =',
112     & ' /* conversion of deg. Centigrade to Kelvin [K] */')
113     CALL WRITE_0D_RL( gravity_mks, INDEX_NONE, 'gravity_mks=',
114     & ' /* gravitational acceleration [m/s^2] */')
115     CALL WRITE_0D_RL( atmrho, INDEX_NONE, 'atmrho =',
116     & ' /* mean atmospheric density [kg/m^3] */')
117     CALL WRITE_0D_RL( atmcp, INDEX_NONE, 'atmcp =',
118     & ' /* mean atmospheric specific heat [J/kg/K] */')
119     CALL WRITE_0D_RL( flamb, INDEX_NONE, 'flamb =',
120     & ' /* latent heat of evaporation [J/kg] */')
121     CALL WRITE_0D_RL( flami, INDEX_NONE, 'flami =',
122     & ' /* latent heat of pure-ice melting [J/kg] */')
123     CALL WRITE_0D_RL( cvapor_fac, INDEX_NONE, 'cvapor_fac =',
124     & ' /* const. for Saturation calculation [?] */')
125     CALL WRITE_0D_RL( cvapor_exp, INDEX_NONE, 'cvapor_exp =',
126     & ' /* const. for Saturation calculation [?] */')
127     CALL WRITE_0D_RL( cvapor_fac_ice, INDEX_NONE, 'cvapor_fac_ice=',
128     & ' /* const. for Saturation calculation [?] */')
129     CALL WRITE_0D_RL( cvapor_exp_ice, INDEX_NONE, 'cvapor_exp_ice=',
130     & ' /* const. for Saturation calculation [?] */')
131     CALL WRITE_0D_RL( humid_fac, INDEX_NONE, 'humid_fac =',
132     & ' /* humidity coef. in virtual temp. [(kg/kg)^-1] */')
133     CALL WRITE_0D_RL( gamma_blk, INDEX_NONE, 'gamma_blk =',
134     & ' /* adiabatic lapse rate [?] */')
135     CALL WRITE_0D_RL( saltsat, INDEX_NONE, 'saltsat =',
136     & ' /* reduction of Qsat over salty water [-] */')
137     CALL WRITE_0D_L( noNegativeEvap,INDEX_NONE,'noNegativeEvap =',
138     & ' /* prevent negative Evaporation */')
139     CALL WRITE_0D_RL( sstExtrapol, INDEX_NONE, 'sstExtrapol =',
140     & ' /* extrapolation coeff from lev. 1 & 2 to surf [-] */')
141     CALL WRITE_0D_RL( cdrag_1, INDEX_NONE, 'cDrag_1 =',
142     & ' /* coef used in drag calculation [?] */')
143     CALL WRITE_0D_RL( cdrag_2, INDEX_NONE, 'cDrag_2 =',
144     & ' /* coef used in drag calculation [?] */')
145     CALL WRITE_0D_RL( cdrag_3, INDEX_NONE, 'cDrag_3 =',
146     & ' /* coef used in drag calculation [?] */')
147     CALL WRITE_0D_RL( cstanton_1, INDEX_NONE, 'cStanton_1 =',
148     & ' /* coef used in Stanton number calculation [?] */')
149     CALL WRITE_0D_RL( cstanton_2, INDEX_NONE, 'cStanton_2 =',
150     & ' /* coef used in Stanton number calculation [?] */')
151     CALL WRITE_0D_RL( cdalton, INDEX_NONE, 'cDalton =',
152     & ' /* coef used in Dalton number calculation [?] */')
153     CALL WRITE_0D_RL( exf_scal_BulkCdn, INDEX_NONE,
154     & 'exf_scal_BulkCdn=',
155     & ' /* Drag coefficient scaling factor [-] */')
156     CALL WRITE_0D_RL( zolmin, INDEX_NONE, 'zolmin =',
157     & ' /* minimum stability parameter [?] */')
158     CALL WRITE_0D_RL( psim_fac, INDEX_NONE, 'psim_fac =',
159     & ' /* coef used in turbulent fluxes calculation [-] */')
160     CALL WRITE_0D_RL( zref, INDEX_NONE, 'zref =',
161     & ' /* reference height [ m ] */')
162     CALL WRITE_0D_RL( hu, INDEX_NONE, 'hu =',
163     & ' /* height of mean wind [ m ] */')
164     CALL WRITE_0D_RL( ht, INDEX_NONE, 'ht =',
165     & ' /* height of mean temperature [ m ] */')
166     CALL WRITE_0D_RL( hq, INDEX_NONE, 'hq =',
167     & ' /* height of mean spec.humidity [ m ] */')
168     CALL WRITE_0D_RL( umin, INDEX_NONE, 'uMin =',
169     & ' /* minimum wind speed [m/s] */')
170     CALL WRITE_0D_L( useStabilityFct_overIce, INDEX_NONE,
171     & 'useStabilityFct_overIce=',
172     & ' /* transfert Coeffs over sea-ice depend on stability */')
173     CALL WRITE_0D_RL( exf_iceCd, INDEX_NONE, 'exf_iceCd =',
174     & ' /* drag coefficient over sea-ice (fixed) [-] */')
175     CALL WRITE_0D_RL( exf_iceCe, INDEX_NONE, 'exf_iceCe =',
176     & ' /* transfert coeff. over sea-ice, for Evap (fixed) [-] */')
177     CALL WRITE_0D_RL( exf_iceCh, INDEX_NONE, 'exf_iceCh =',
178     & ' /* transfert coeff. over sea-ice, Sens.Heat.(fixed)[-] */')
179     CALL WRITE_0D_RL( exf_albedo, INDEX_NONE, 'exf_albedo =',
180     & ' /* Sea-water albedo [-] */')
181     CALL WRITE_0D_L( useExfZenAlbedo, INDEX_NONE, 'useExfZenAlbedo =',
182     & ' /* Sea-water albedo varies with zenith angle */')
183     CALL WRITE_0D_I( select_ZenAlbedo,INDEX_NONE,'select_ZenAlbedo =',
184     & ' /* Sea-water albedo computation method */')
185     CALL WRITE_0D_L( useExfZenIncoming, INDEX_NONE,
186     & 'useExfZenIncoming =',' /* compute incoming solar radiation */')
187     CALL WRITE_0D_RL( ocean_emissivity, INDEX_NONE,
188     & 'ocean_emissivity =',
189     & ' /* longwave ocean-surface emissivity [-] */')
190     CALL WRITE_0D_RL( ice_emissivity, INDEX_NONE,'ice_emissivity =',
191     & ' /* longwave seaice emissivity [-] */')
192     CALL WRITE_0D_RL(snow_emissivity, INDEX_NONE,'snow_emissivity =',
193     & ' /* longwave snow emissivity [-] */')
194     WRITE(msgBuf,'(A)') ' '
195     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
196     & SQUEEZE_RIGHT , myThid )
197    
198     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
199     C-- Print settings of some CPP flags.
200     WRITE(msgBuf,'(A)') ' EXF main CPP flags:'
201     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
202     & SQUEEZE_RIGHT , myThid )
203     WRITE(msgBuf,'(A)') ' '
204     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
205     & SQUEEZE_RIGHT , myThid )
206    
207     #ifdef ALLOW_ATM_TEMP
208     write(msgbuf,'(a)')
209     &'// ALLOW_ATM_TEMP: defined'
210     call print_message( msgbuf, standardmessageunit,
211     & SQUEEZE_RIGHT , mythid)
212     #else
213     write(msgbuf,'(a)')
214     &'// ALLOW_ATM_TEMP: NOT defined'
215     call print_message( msgbuf, standardmessageunit,
216     & SQUEEZE_RIGHT , mythid)
217     #endif
218    
219     #ifdef ALLOW_ATM_WIND
220     write(msgbuf,'(a)')
221     &'// ALLOW_ATM_WIND: defined'
222     call print_message( msgbuf, standardmessageunit,
223     & SQUEEZE_RIGHT , mythid)
224     #else
225     write(msgbuf,'(a)')
226     &'// ALLOW_ATM_WIND: NOT defined'
227     call print_message( msgbuf, standardmessageunit,
228     & SQUEEZE_RIGHT , mythid)
229     #endif
230    
231     #ifdef ALLOW_DOWNWARD_RADIATION
232     write(msgbuf,'(a)')
233     &'// ALLOW_DOWNWARD_RADIATION: defined'
234     call print_message( msgbuf, standardmessageunit,
235     & SQUEEZE_RIGHT , mythid)
236     #else
237     write(msgbuf,'(a)')
238     &'// ALLOW_DOWNWARD_RADIATION: NOT defined'
239     call print_message( msgbuf, standardmessageunit,
240     & SQUEEZE_RIGHT , mythid)
241     #endif
242    
243     #ifdef ALLOW_BULKFORMULAE
244     write(msgbuf,'(a)')
245     &'// ALLOW_BULKFORMULAE: defined'
246     call print_message( msgbuf, standardmessageunit,
247     & SQUEEZE_RIGHT , mythid)
248     #else
249     write(msgbuf,'(a)')
250     &'// ALLOW_BULKFORMULAE: NOT defined'
251     call print_message( msgbuf, standardmessageunit,
252     & SQUEEZE_RIGHT , mythid)
253     #endif
254    
255     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
256    
257     C-- For each data set used the summary prints the calendar data
258     C and the corresponding file from which the data will be read.
259    
260     #ifndef ALLOW_ATM_WIND
261     C-- Zonal wind stress.
262     il = ilnblnk(ustressfile)
263     write(msgbuf,'(a)') ' '
264     call print_message( msgbuf, standardmessageunit,
265     & SQUEEZE_RIGHT , mythid)
266     write(msgbuf,'(a,f12.0)')
267     &' Zonal wind stress forcing starts at ',
268     & ustressstartdate
269     call print_message( msgbuf, standardmessageunit,
270     & SQUEEZE_RIGHT , mythid)
271     write(msgbuf,'(a,f12.0)')
272     &' Zonal wind stress forcing period is ',
273     & ustressperiod
274     call print_message( msgbuf, standardmessageunit,
275     & SQUEEZE_RIGHT , mythid)
276     write(msgbuf,'(a)')
277     &' Zonal wind stress forcing is read from file:'
278     call print_message( msgbuf, standardmessageunit,
279     & SQUEEZE_RIGHT , mythid)
280     write(msgbuf,'(a,a,a)')
281     &' >> ',ustressfile(1:il),' <<'
282     call print_message( msgbuf, standardmessageunit,
283     & SQUEEZE_RIGHT , mythid)
284    
285     C-- Meridional wind stress.
286     il = ilnblnk(vstressfile)
287     write(msgbuf,'(a)') ' '
288     call print_message( msgbuf, standardmessageunit,
289     & SQUEEZE_RIGHT , mythid)
290     write(msgbuf,'(a,f12.0)')
291     &' Meridional wind stress forcing starts at ',
292     & vstressstartdate
293     call print_message( msgbuf, standardmessageunit,
294     & SQUEEZE_RIGHT , mythid)
295     write(msgbuf,'(a,f12.0)')
296     &' Meridional wind stress forcing period is ',
297     & vstressperiod
298     call print_message( msgbuf, standardmessageunit,
299     & SQUEEZE_RIGHT , mythid)
300     write(msgbuf,'(a)')
301     &' Meridional wind stress forcing is read from file:'
302     call print_message( msgbuf, standardmessageunit,
303     & SQUEEZE_RIGHT , mythid)
304     write(msgbuf,'(a,a,a)')
305     &' >> ',vstressfile(1:il),' <<'
306     call print_message( msgbuf, standardmessageunit,
307     & SQUEEZE_RIGHT , mythid)
308     #endif
309    
310     #ifndef ALLOW_ATM_TEMP
311     C-- Heat flux.
312     il = ilnblnk(hfluxfile)
313     write(msgbuf,'(a)') ' '
314     call print_message( msgbuf, standardmessageunit,
315     & SQUEEZE_RIGHT , mythid)
316     write(msgbuf,'(a,f12.0)')
317     &' Heat flux forcing starts at ',
318     & hfluxstartdate
319     call print_message( msgbuf, standardmessageunit,
320     & SQUEEZE_RIGHT , mythid)
321     write(msgbuf,'(a,f12.0)')
322     &' Heat flux forcing period is ',
323     & hfluxperiod
324     call print_message( msgbuf, standardmessageunit,
325     & SQUEEZE_RIGHT , mythid)
326     write(msgbuf,'(a)')
327     &' Heat flux forcing is read from file: '
328     call print_message( msgbuf, standardmessageunit,
329     & SQUEEZE_RIGHT , mythid)
330     write(msgbuf,'(a,a,a)')
331     &' >> ',hfluxfile(1:il),' <<'
332     call print_message( msgbuf, standardmessageunit,
333     & SQUEEZE_RIGHT , mythid)
334    
335     C-- Salt flux.
336     il = ilnblnk(sfluxfile)
337     write(msgbuf,'(a)') ' '
338     call print_message( msgbuf, standardmessageunit,
339     & SQUEEZE_RIGHT , mythid)
340     write(msgbuf,'(a,f12.0)')
341     &' Salt flux forcing starts at ',
342     & sfluxstartdate
343     call print_message( msgbuf, standardmessageunit,
344     & SQUEEZE_RIGHT , mythid)
345     write(msgbuf,'(a,f12.0)')
346     &' Salt flux forcing period is ',
347     & sfluxperiod
348     call print_message( msgbuf, standardmessageunit,
349     & SQUEEZE_RIGHT , mythid)
350     write(msgbuf,'(a)')
351     &' Salt flux forcing is read from file: '
352     call print_message( msgbuf, standardmessageunit,
353     & SQUEEZE_RIGHT , mythid)
354     write(msgbuf,'(a,a,a)')
355     &' >> ',sfluxfile(1:il),' <<'
356     call print_message( msgbuf, standardmessageunit,
357     & SQUEEZE_RIGHT , mythid)
358     #endif
359    
360     #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
361     C-- Net shortwave.
362     il = ilnblnk(swfluxfile)
363     write(msgbuf,'(a)') ' '
364     call print_message( msgbuf, standardmessageunit,
365     & SQUEEZE_RIGHT , mythid)
366     write(msgbuf,'(a,f12.0)')
367     &' Net shortwave flux forcing starts at ',
368     & swfluxstartdate
369     call print_message( msgbuf, standardmessageunit,
370     & SQUEEZE_RIGHT , mythid)
371     write(msgbuf,'(a,f12.0)')
372     &' Net shortwave flux forcing period is ',
373     & swfluxperiod
374     call print_message( msgbuf, standardmessageunit,
375     & SQUEEZE_RIGHT , mythid)
376     write(msgbuf,'(a)')
377     &' Net shortwave flux forcing is read from file:'
378     call print_message( msgbuf, standardmessageunit,
379     & SQUEEZE_RIGHT , mythid)
380     write(msgbuf,'(a,a,a)')
381     &' >> ',swfluxfile(1:il),' <<'
382     call print_message( msgbuf, standardmessageunit,
383     & SQUEEZE_RIGHT , mythid)
384     #endif
385    
386     #ifdef ALLOW_ATM_WIND
387     C-- Zonal wind.
388     il = ilnblnk(uwindfile)
389     write(msgbuf,'(a)') ' '
390     call print_message( msgbuf, standardmessageunit,
391     & SQUEEZE_RIGHT , mythid)
392     write(msgbuf,'(a,f12.0)')
393     &' Zonal wind forcing starts at ',
394     & uwindstartdate
395     call print_message( msgbuf, standardmessageunit,
396     & SQUEEZE_RIGHT , mythid)
397     write(msgbuf,'(a,f12.0)')
398     &' Zonal wind forcing period is ',
399     & uwindperiod
400     call print_message( msgbuf, standardmessageunit,
401     & SQUEEZE_RIGHT , mythid)
402     write(msgbuf,'(a)')
403     &' Zonal wind forcing is read from file:'
404     call print_message( msgbuf, standardmessageunit,
405     & SQUEEZE_RIGHT , mythid)
406     write(msgbuf,'(a,a,a)')
407     &' >> ',uwindfile(1:il),' <<'
408     call print_message( msgbuf, standardmessageunit,
409     & SQUEEZE_RIGHT , mythid)
410    
411     C-- Meridional wind.
412     il = ilnblnk(vwindfile)
413     write(msgbuf,'(a)') ' '
414     call print_message( msgbuf, standardmessageunit,
415     & SQUEEZE_RIGHT , mythid)
416     write(msgbuf,'(a,f12.0)')
417     &' Meridional wind forcing starts at ',
418     & vwindstartdate
419     call print_message( msgbuf, standardmessageunit,
420     & SQUEEZE_RIGHT , mythid)
421     write(msgbuf,'(a,f12.0)')
422     &' Meridional wind forcing period is ',
423     & vwindperiod
424     call print_message( msgbuf, standardmessageunit,
425     & SQUEEZE_RIGHT , mythid)
426     write(msgbuf,'(a)')
427     &' Meridional wind forcing is read from file:'
428     call print_message( msgbuf, standardmessageunit,
429     & SQUEEZE_RIGHT , mythid)
430     write(msgbuf,'(a,a,a)')
431     &' >> ',vwindfile(1:il),' <<'
432     call print_message( msgbuf, standardmessageunit,
433     & SQUEEZE_RIGHT , mythid)
434     #endif
435    
436     #ifdef ALLOW_ATM_TEMP
437     C-- Atmospheric temperature.
438     il = ilnblnk(atempfile)
439     write(msgbuf,'(a)') ' '
440     call print_message( msgbuf, standardmessageunit,
441     & SQUEEZE_RIGHT , mythid)
442     write(msgbuf,'(a,f12.0)')
443     &' Atmospheric temperature starts at ',
444     & atempstartdate
445     call print_message( msgbuf, standardmessageunit,
446     & SQUEEZE_RIGHT , mythid)
447     write(msgbuf,'(a,f12.0)')
448     &' Atmospheric temperature period is ',
449     & atempperiod
450     call print_message( msgbuf, standardmessageunit,
451     & SQUEEZE_RIGHT , mythid)
452     write(msgbuf,'(a)')
453     &' Atmospheric temperature is read from file:'
454     call print_message( msgbuf, standardmessageunit,
455     & SQUEEZE_RIGHT , mythid)
456     write(msgbuf,'(a,a,a)')
457     &' >> ',atempfile(1:il),' <<'
458     call print_message( msgbuf, standardmessageunit,
459     & SQUEEZE_RIGHT , mythid)
460    
461     C-- Atmospheric specific humidity.
462     il = ilnblnk(aqhfile)
463     write(msgbuf,'(a)') ' '
464     call print_message( msgbuf, standardmessageunit,
465     & SQUEEZE_RIGHT , mythid)
466     write(msgbuf,'(a,f12.0)')
467     &' Atmospheric specific humidity starts at ',
468     & aqhstartdate
469     call print_message( msgbuf, standardmessageunit,
470     & SQUEEZE_RIGHT , mythid)
471     write(msgbuf,'(a,f12.0)')
472     &' Atmospheric specific humidity period is ',
473     & aqhperiod
474     call print_message( msgbuf, standardmessageunit,
475     & SQUEEZE_RIGHT , mythid)
476     write(msgbuf,'(a)')
477     &' Atmospheric specific humidity is read from file:'
478     call print_message( msgbuf, standardmessageunit,
479     & SQUEEZE_RIGHT , mythid)
480     write(msgbuf,'(a,a,a)')
481     &' >> ',aqhfile(1:il),' <<'
482     call print_message( msgbuf, standardmessageunit,
483     & SQUEEZE_RIGHT , mythid)
484    
485     C-- Net longwave.
486     il = ilnblnk(lwfluxfile)
487     write(msgbuf,'(a)') ' '
488     call print_message( msgbuf, standardmessageunit,
489     & SQUEEZE_RIGHT , mythid)
490     write(msgbuf,'(a,f12.0)')
491     &' Net longwave flux forcing starts at ',
492     & lwfluxstartdate
493     call print_message( msgbuf, standardmessageunit,
494     & SQUEEZE_RIGHT , mythid)
495     write(msgbuf,'(a,f12.0)')
496     &' Net longwave flux forcing period is ',
497     & lwfluxperiod
498     call print_message( msgbuf, standardmessageunit,
499     & SQUEEZE_RIGHT , mythid)
500     write(msgbuf,'(a)')
501     &' Net longwave flux forcing is read from file:'
502     call print_message( msgbuf, standardmessageunit,
503     & SQUEEZE_RIGHT , mythid)
504     write(msgbuf,'(a,a,a)')
505     &' >> ',lwfluxfile(1:il),' <<'
506     call print_message( msgbuf, standardmessageunit,
507     & SQUEEZE_RIGHT , mythid)
508    
509     C-- Precipitation.
510     il = ilnblnk(precipfile)
511     write(msgbuf,'(a)') ' '
512     call print_message( msgbuf, standardmessageunit,
513     & SQUEEZE_RIGHT , mythid)
514     write(msgbuf,'(a,f12.0)')
515     &' Precipitation data set starts at ',
516     & precipstartdate
517     call print_message( msgbuf, standardmessageunit,
518     & SQUEEZE_RIGHT , mythid)
519     write(msgbuf,'(a,f12.0)')
520     &' Precipitation data period is ',
521     & precipperiod
522     call print_message( msgbuf, standardmessageunit,
523     & SQUEEZE_RIGHT , mythid)
524     write(msgbuf,'(a)')
525     &' Precipitation data is read from file: '
526     call print_message( msgbuf, standardmessageunit,
527     & SQUEEZE_RIGHT , mythid)
528     write(msgbuf,'(a,a,a)')
529     &' >> ',precipfile(1:il),' <<'
530     call print_message( msgbuf, standardmessageunit,
531     & SQUEEZE_RIGHT , mythid)
532     #endif
533    
534     C-- Evaporation.
535     write(msgbuf,'(a)') ' '
536     call print_message( msgbuf, standardmessageunit,
537     & SQUEEZE_RIGHT , mythid)
538     #ifdef EXF_READ_EVAP
539     write(msgbuf,'(a)')
540     &'// EXF_READ_EVAP: defined'
541     call print_message( msgbuf, standardmessageunit,
542     & SQUEEZE_RIGHT , mythid)
543     il = ilnblnk(evapfile)
544     write(msgbuf,'(a,f12.0)')
545     &' Evaporation starts at ',
546     & evapstartdate
547     call print_message( msgbuf, standardmessageunit,
548     & SQUEEZE_RIGHT , mythid)
549     write(msgbuf,'(a,f12.0)')
550     &' Evaporation period is ',
551     & evapperiod
552     call print_message( msgbuf, standardmessageunit,
553     & SQUEEZE_RIGHT , mythid)
554     write(msgbuf,'(a)')
555     &' Evaporation is read from file:'
556     call print_message( msgbuf, standardmessageunit,
557     & SQUEEZE_RIGHT , mythid)
558     write(msgbuf,'(a,a,a)')
559     &' >> ',evapfile(1:il),' <<'
560     call print_message( msgbuf, standardmessageunit,
561     & SQUEEZE_RIGHT , mythid)
562     #else
563     write(msgbuf,'(a)')
564     &'// EXF_READ_EVAP: NOT defined'
565     call print_message( msgbuf, standardmessageunit,
566     & SQUEEZE_RIGHT , mythid)
567     #endif
568    
569     C-- Runoff.
570     write(msgbuf,'(a)') ' '
571     call print_message( msgbuf, standardmessageunit,
572     & SQUEEZE_RIGHT , mythid)
573     #ifdef ALLOW_RUNOFF
574     write(msgbuf,'(a)')
575     &'// ALLOW_RUNOFF: defined'
576     call print_message( msgbuf, standardmessageunit,
577     & SQUEEZE_RIGHT , mythid)
578     il = ilnblnk(runofffile)
579     write(msgbuf,'(a,f12.0)')
580     &' Runoff starts at ',
581     & runoffstartdate
582     call print_message( msgbuf, standardmessageunit,
583     & SQUEEZE_RIGHT , mythid)
584     write(msgbuf,'(a,f12.0)')
585     &' Runoff period is ',
586     & runoffperiod
587     call print_message( msgbuf, standardmessageunit,
588     & SQUEEZE_RIGHT , mythid)
589     write(msgbuf,'(a)')
590     &' Runoff is read from file:'
591     call print_message( msgbuf, standardmessageunit,
592     & SQUEEZE_RIGHT , mythid)
593     write(msgbuf,'(a,a,a)')
594     &' >> ',runofffile(1:il),' <<'
595     call print_message( msgbuf, standardmessageunit,
596     & SQUEEZE_RIGHT , mythid)
597     #else /* ALLOW_RUNOFF */
598     write(msgbuf,'(a)')
599     &'// ALLOW_RUNOFF: NOT defined'
600     call print_message( msgbuf, standardmessageunit,
601     & SQUEEZE_RIGHT , mythid)
602     #endif /* ALLOW_RUNOFF */
603    
604     #ifdef ALLOW_DOWNWARD_RADIATION
605     C-- Downward shortwave.
606     il = ilnblnk(swdownfile)
607     write(msgbuf,'(a)') ' '
608     call print_message( msgbuf, standardmessageunit,
609     & SQUEEZE_RIGHT , mythid)
610     write(msgbuf,'(a,f12.0)')
611     &' Downward shortwave flux forcing starts at ',
612     & swdownstartdate
613     call print_message( msgbuf, standardmessageunit,
614     & SQUEEZE_RIGHT , mythid)
615     write(msgbuf,'(a,f12.0)')
616     &' Downward shortwave flux forcing period is ',
617     & swdownperiod
618     call print_message( msgbuf, standardmessageunit,
619     & SQUEEZE_RIGHT , mythid)
620     write(msgbuf,'(a)')
621     &' Downward shortwave flux forcing is read from file:'
622     call print_message( msgbuf, standardmessageunit,
623     & SQUEEZE_RIGHT , mythid)
624     write(msgbuf,'(a,a,a)')
625     &' >> ',swdownfile(1:il),' <<'
626     call print_message( msgbuf, standardmessageunit,
627     & SQUEEZE_RIGHT , mythid)
628    
629     C-- Downward longwave.
630     il = ilnblnk(lwdownfile)
631     write(msgbuf,'(a)') ' '
632     call print_message( msgbuf, standardmessageunit,
633     & SQUEEZE_RIGHT , mythid)
634     write(msgbuf,'(a,f12.0)')
635     &' Downward longwave flux forcing starts at ',
636     & lwdownstartdate
637     call print_message( msgbuf, standardmessageunit,
638     & SQUEEZE_RIGHT , mythid)
639     write(msgbuf,'(a,f12.0)')
640     &' Downward longwave flux forcing period is ',
641     & lwdownperiod
642     call print_message( msgbuf, standardmessageunit,
643     & SQUEEZE_RIGHT , mythid)
644     write(msgbuf,'(a)')
645     &' Downward longwave flux forcing is read from file:'
646     call print_message( msgbuf, standardmessageunit,
647     & SQUEEZE_RIGHT , mythid)
648     write(msgbuf,'(a,a,a)')
649     &' >> ',lwdownfile(1:il),' <<'
650     call print_message( msgbuf, standardmessageunit,
651     & SQUEEZE_RIGHT , mythid)
652     #endif
653    
654     #ifdef ATMOSPHERIC_LOADING
655     C-- Atmospheric pressure.
656     il = ilnblnk(apressurefile)
657     write(msgbuf,'(a)') ' '
658     call print_message( msgbuf, standardmessageunit,
659     & SQUEEZE_RIGHT , mythid)
660     write(msgbuf,'(a,f12.0)')
661     &' Atmospheric pressure forcing starts at ',
662     & apressurestartdate
663     call print_message( msgbuf, standardmessageunit,
664     & SQUEEZE_RIGHT , mythid)
665     write(msgbuf,'(a,f12.0)')
666     &' Atmospheric pressure forcing period is ',
667     & apressureperiod
668     call print_message( msgbuf, standardmessageunit,
669     & SQUEEZE_RIGHT , mythid)
670     write(msgbuf,'(a)')
671     &' Atmospheric pressureforcing is read from file:'
672     call print_message( msgbuf, standardmessageunit,
673     & SQUEEZE_RIGHT , mythid)
674     write(msgbuf,'(a,a,a)')
675     &' >> ',apressurefile(1:il),' <<'
676     call print_message( msgbuf, standardmessageunit,
677     & SQUEEZE_RIGHT , mythid)
678     #endif
679    
680     #ifdef ALLOW_ICE_AREAMASK
681     C-- fractional ice-covered area MASK.
682     il = ilnblnk(areamaskfile)
683     write(msgbuf,'(a)') ' '
684     call print_message( msgbuf, standardmessageunit,
685     & SQUEEZE_RIGHT , mythid)
686     write(msgbuf,'(a,f12.0)')
687     &' fractional ice-covered area MASK starts at ',
688     & areamaskstartdate
689     call print_message( msgbuf, standardmessageunit,
690     & SQUEEZE_RIGHT , mythid)
691     write(msgbuf,'(a,f12.0)')
692     &' fractional ice-covered area MASK period is ',
693     & areamaskperiod
694     call print_message( msgbuf, standardmessageunit,
695     & SQUEEZE_RIGHT , mythid)
696     write(msgbuf,'(a)')
697     &' fractional ice-covered area MASK is read from file:'
698     call print_message( msgbuf, standardmessageunit,
699     & SQUEEZE_RIGHT , mythid)
700     write(msgbuf,'(a,a,a)')
701     &' >> ',areamaskfile(1:il),' <<'
702     call print_message( msgbuf, standardmessageunit,
703     & SQUEEZE_RIGHT , mythid)
704     #endif
705    
706     #ifdef ALLOW_CARBON
707     #ifdef USE_EXFCO2
708     C-- Atmospheric pCO2
709     il = ilnblnk(apco2file)
710     write(msgbuf,'(a)') ' '
711     call print_message( msgbuf, standardmessageunit,
712     & SQUEEZE_RIGHT , mythid)
713     write(msgbuf,'(a,f12.0)')
714     &' Atmospheric pCO2 forcing starts at ',
715     & apco2startdate
716     call print_message( msgbuf, standardmessageunit,
717     & SQUEEZE_RIGHT , mythid)
718     write(msgbuf,'(a,f12.0)')
719     &' Atmospheric pCO2 forcing period is ',
720     & apco2period
721     call print_message( msgbuf, standardmessageunit,
722     & SQUEEZE_RIGHT , mythid)
723     write(msgbuf,'(a)')
724     &' Atmospheric pCO2 forcing is read from file:'
725     call print_message( msgbuf, standardmessageunit,
726     & SQUEEZE_RIGHT , mythid)
727     write(msgbuf,'(a,a,a)')
728     &' >> ',apco2file(1:il),' <<'
729     call print_message( msgbuf, standardmessageunit,
730     & SQUEEZE_RIGHT , mythid)
731     #endif
732     #endif
733    
734     write(msgbuf,'(a)') ' '
735     call print_message( msgbuf, standardmessageunit,
736     & SQUEEZE_RIGHT , mythid)
737     write(msgbuf,'(a)')
738     &'// ======================================================='
739     call print_message( msgbuf, standardmessageunit,
740     & SQUEEZE_RIGHT , mythid)
741     write(msgbuf,'(a)')
742     &'// External forcing configuration >>> END <<<'
743     call print_message( msgbuf, standardmessageunit,
744     & SQUEEZE_RIGHT , mythid)
745     write(msgbuf,'(a)')
746     &'// ======================================================='
747     call print_message( msgbuf, standardmessageunit,
748     & SQUEEZE_RIGHT , mythid)
749     write(msgbuf,'(a)') ' '
750     call print_message( msgbuf, standardmessageunit,
751     & SQUEEZE_RIGHT , mythid)
752    
753     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
754    
755     call print_message( msgbuf, standardmessageunit,
756     & SQUEEZE_RIGHT , mythid)
757     write(msgbuf,'(a)')
758     &'// ======================================================='
759     call print_message( msgbuf, standardmessageunit,
760     & SQUEEZE_RIGHT , mythid)
761     write(msgbuf,'(a)')
762     &'// External forcing climatology configuration >>> START <<<'
763     call print_message( msgbuf, standardmessageunit,
764     & SQUEEZE_RIGHT , mythid)
765     write(msgbuf,'(a)')
766     &'// ======================================================='
767     call print_message( msgbuf, standardmessageunit,
768     & SQUEEZE_RIGHT , mythid)
769     write(msgbuf,'(a)') ' '
770     call print_message( msgbuf, standardmessageunit,
771     & SQUEEZE_RIGHT , mythid)
772    
773     C For each data set used the summary prints the calendar data
774     C and the corresponding file from which the data will be read.
775    
776     #ifdef ALLOW_CLIMSST_RELAXATION
777     write(msgbuf,'(a)')
778     &'// ALLOW_CLIMSST_RELAXATION: defined'
779     call print_message( msgbuf, standardmessageunit,
780     & SQUEEZE_RIGHT , mythid)
781     #else
782     write(msgbuf,'(a)')
783     &'// ALLOW_CLIMSST_RELAXATION: NOT defined'
784     call print_message( msgbuf, standardmessageunit,
785     & SQUEEZE_RIGHT , mythid)
786     #endif
787    
788     #ifdef ALLOW_CLIMSSS_RELAXATION
789     write(msgbuf,'(a)')
790     &'// ALLOW_CLIMSSS_RELAXATION: defined'
791     call print_message( msgbuf, standardmessageunit,
792     & SQUEEZE_RIGHT , mythid)
793     #else
794     write(msgbuf,'(a)')
795     &'// ALLOW_CLIMSSS_RELAXATION: NOT defined'
796     call print_message( msgbuf, standardmessageunit,
797     & SQUEEZE_RIGHT , mythid)
798     #endif
799    
800     C The climatological data sets are assumed to contain monthly
801     C data. This can be changed in a later version to an arbitrary
802     C number of intervals during a given year.
803    
804     #ifdef ALLOW_CLIMSST_RELAXATION
805     C Relaxation to SST climatology.
806     il = ilnblnk(climsstfile)
807     write(msgbuf,'(a)')
808     &' '
809     call print_message( msgbuf, standardmessageunit,
810     & SQUEEZE_RIGHT , mythid)
811     write(msgbuf,'(a,f12.0)')
812     &' Climatological SST starts at ',
813     & climsststartdate
814     call print_message( msgbuf, standardmessageunit,
815     & SQUEEZE_RIGHT , mythid)
816     write(msgbuf,'(a,f12.0)')
817     &' Climatological SST period is ',
818     & climsstperiod
819     call print_message( msgbuf, standardmessageunit,
820     & SQUEEZE_RIGHT , mythid)
821     write(msgbuf,'(a)')
822     &' Climatological SST is read from file:'
823     call print_message( msgbuf, standardmessageunit,
824     & SQUEEZE_RIGHT , mythid)
825     write(msgbuf,'(a,a,a)')
826     &' >> ',climsstfile(1:il),' <<'
827     call print_message( msgbuf, standardmessageunit,
828     & SQUEEZE_RIGHT , mythid)
829     #endif
830    
831     #ifdef ALLOW_CLIMSSS_RELAXATION
832     C Relaxation to SSS climatology.
833     il = ilnblnk(climsssfile)
834     write(msgbuf,'(a)')
835     &' '
836     call print_message( msgbuf, standardmessageunit,
837     & SQUEEZE_RIGHT , mythid)
838     write(msgbuf,'(a,f12.0)')
839     &' Climatological SSS starts at ',
840     & climsssstartdate
841     call print_message( msgbuf, standardmessageunit,
842     & SQUEEZE_RIGHT , mythid)
843     write(msgbuf,'(a,f12.0)')
844     &' Climatological SSS period is ',
845     & climsssperiod
846     call print_message( msgbuf, standardmessageunit,
847     & SQUEEZE_RIGHT , mythid)
848     write(msgbuf,'(a)')
849     &' Climatological SSS is read from file:'
850     call print_message( msgbuf, standardmessageunit,
851     & SQUEEZE_RIGHT , mythid)
852     write(msgbuf,'(a,a,a)')
853     &' >> ',climsssfile(1:il),' <<'
854     call print_message( msgbuf, standardmessageunit,
855     & SQUEEZE_RIGHT , mythid)
856     #endif
857    
858     write(msgbuf,'(a)') ' '
859     call print_message( msgbuf, standardmessageunit,
860     & SQUEEZE_RIGHT , mythid)
861     write(msgbuf,'(a)')
862     &'// ======================================================='
863     call print_message( msgbuf, standardmessageunit,
864     & SQUEEZE_RIGHT , mythid)
865     write(msgbuf,'(a)')
866     &'// External forcing climatology configuration >>> END <<<'
867     call print_message( msgbuf, standardmessageunit,
868     & SQUEEZE_RIGHT , mythid)
869     write(msgbuf,'(a)')
870     &'// ======================================================='
871     call print_message( msgbuf, standardmessageunit,
872     & SQUEEZE_RIGHT , mythid)
873     write(msgbuf,'(a)') ' '
874     call print_message( msgbuf, standardmessageunit,
875     & SQUEEZE_RIGHT , mythid)
876    
877     _END_MASTER( myThid )
878    
879     RETURN
880     END

  ViewVC Help
Powered by ViewVC 1.1.22