/[MITgcm]/MITgcm_contrib/dcarroll/highres_darwin/code/exf_summary.F
ViewVC logotype

Annotation of /MITgcm_contrib/dcarroll/highres_darwin/code/exf_summary.F

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


Revision 1.1 - (hide annotations) (download)
Sun Sep 22 21:23:46 2019 UTC (5 years, 10 months ago) by dcarroll
Branch: MAIN
CVS Tags: HEAD
Initial check in of high resolution Darwin simulation code

1 dcarroll 1.1 C $Header: /u/gcmpack/MITgcm_contrib/ecco_darwin/v4_llc270/code_darwin/exf_summary.F,v 1.1 2017/12/01 19:02:11 dimitri Exp $
2     C $Name: $
3    
4     #include "EXF_OPTIONS.h"
5    
6     C-- File exf_summary.F: Routines to print out EXF settings
7     C-- Contents
8     C-- o EXF_SUMMARY
9     C-- o EXF_FLD_SUMMARY
10     C-- o EXF_PRINT_INTERP
11    
12     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
13     CBOP
14     C !ROUTINE: EXF_SUMMARY( myThid )
15     C !INTERFACE:
16    
17     SUBROUTINE EXF_SUMMARY( myThid )
18    
19     C !DESCRIPTION: \bv
20     C ==================================================================
21     C SUBROUTINE exf_summary
22     C ==================================================================
23     C
24     C o List all the settings of the external forcing.
25     C
26     C started: Christian Eckert eckert@mit.edu 11-Jan-1999
27     C
28     C changed: Christian Eckert eckert@mit.edu 12-Feb-2000
29     C - changed routine names (package prefix: exf_)
30     C
31     C changed: Patrick Heimbach heimbach@mit.edu 04-May-2000
32     C - changed the handling of precip and sflux with respect
33     C to CPP options ALLOW_BULKFORMULAE and ALLOW_ATM_TEMP
34     C
35     C changed: Dimitris Menemenlis menemenlis@jpl.nasa.gov 20-Dec-2002
36     C - modifications for using pkg/exf with pkg/seaice
37     C
38     C ==================================================================
39     C SUBROUTINE exf_summary
40     C ==================================================================
41     C \ev
42    
43     C !USES:
44     IMPLICIT NONE
45    
46     C === Global variables ===
47     #include "EEPARAMS.h"
48     #include "SIZE.h"
49     #include "EXF_CONSTANTS.h"
50     #include "EXF_PARAM.h"
51    
52     C !INPUT/OUTPUT PARAMETERS:
53     C myThid :: My thread Id number
54     INTEGER myThid
55    
56     C !FUNCTIONS:
57     INTEGER ILNBLNK
58     EXTERNAL ILNBLNK
59    
60     C !LOCAL VARIABLES:
61     INTEGER il
62     LOGICAL prtBlkLn, addBlkLn
63     CHARACTER*1 blkLin
64     CHARACTER*(MAX_LEN_MBUF) msgBuf
65     CEOP
66    
67     _BEGIN_MASTER( myThid )
68    
69     blkLin = ' '
70     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
71     & SQUEEZE_RIGHT, myThid )
72     WRITE(msgBuf,'(A)')
73     &'// ======================================================='
74     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
75     & SQUEEZE_RIGHT, myThid )
76     WRITE(msgBuf,'(A)')
77     &'// External forcing (EXF) configuration >>> START <<<'
78     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
79     & SQUEEZE_RIGHT, myThid )
80     WRITE(msgBuf,'(A)')
81     &'// ======================================================='
82     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
83     & SQUEEZE_RIGHT, myThid )
84     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
85     & SQUEEZE_RIGHT, myThid )
86    
87     C-- Print general parameters:
88     WRITE(msgBuf,'(A)') ' EXF general parameters:'
89     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
90     & SQUEEZE_RIGHT , myThid )
91     WRITE(msgBuf,'(A)') ' '
92     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
93     & SQUEEZE_RIGHT , myThid )
94     CALL WRITE_0D_I( exf_iprec, INDEX_NONE, 'exf_iprec =',
95     & ' /* exf file precision */')
96     CALL WRITE_0D_L( useExfYearlyFields, INDEX_NONE,
97     & 'useExfYearlyFields =',
98     & ' /* add extension _YEAR to input file names */')
99     CALL WRITE_0D_L( twoDigitYear, INDEX_NONE, 'twoDigitYear =',
100     & ' /* use 2-digit year extension */')
101     CALL WRITE_0D_L( useExfCheckRange, INDEX_NONE,
102     & 'useExfCheckRange =', ' /* check for fields range */')
103     #ifdef USE_EXF_INTERPOLATION
104     CALL WRITE_0D_L( exf_output_interp, INDEX_NONE,
105     & 'exf_output_interp =',
106     & ' /* output directly interpolation result */')
107     #endif
108     CALL WRITE_0D_I( exf_debugLev, INDEX_NONE, 'exf_debugLev =',
109     & ' /* select EXF-debug printing level */')
110     CALL WRITE_0D_RL( exf_monFreq, INDEX_NONE, 'exf_monFreq =',
111     & ' /* EXF monitor frequency [ s ] */')
112     CALL WRITE_0D_RL( repeatPeriod, INDEX_NONE, 'repeatPeriod =',
113     & ' /* period for cycling forcing dataset [ s ] */')
114     CALL WRITE_0D_RL( climtempfreeze, INDEX_NONE,'climTempFreeze=',
115     & ' /* Minimum climatological temperature [deg.C] */')
116     CALL WRITE_0D_RL( windStressMax, INDEX_NONE,'windStressMax =',
117     & ' /* Maximum absolute windstress [ Pa ] */')
118     CALL WRITE_0D_L( stressIsOnCgrid,INDEX_NONE,'stressIsOnCgrid =',
119     & ' /* set u,v_stress on Arakawa C-grid */')
120     CALL WRITE_0D_L( rotateStressOnAgrid,INDEX_NONE,
121     & 'rotateStressOnAgrid =',
122     & ' /* rotate u,v_stress on Arakawa A-grid */')
123     CALL WRITE_0D_RL( cen2kel, INDEX_NONE, 'cen2kel =',
124     & ' /* conversion of deg. Centigrade to Kelvin [K] */')
125     CALL WRITE_0D_RL( gravity_mks, INDEX_NONE, 'gravity_mks=',
126     & ' /* gravitational acceleration [m/s^2] */')
127     CALL WRITE_0D_RL( atmrho, INDEX_NONE, 'atmrho =',
128     & ' /* mean atmospheric density [kg/m^3] */')
129     CALL WRITE_0D_RL( atmcp, INDEX_NONE, 'atmcp =',
130     & ' /* mean atmospheric specific heat [J/kg/K] */')
131     CALL WRITE_0D_RL( flamb, INDEX_NONE, 'flamb =',
132     & ' /* latent heat of evaporation [J/kg] */')
133     CALL WRITE_0D_RL( flami, INDEX_NONE, 'flami =',
134     & ' /* latent heat of pure-ice melting [J/kg] */')
135     CALL WRITE_0D_RL( cvapor_fac, INDEX_NONE, 'cvapor_fac =',
136     & ' /* const. for Saturation calculation [?] */')
137     CALL WRITE_0D_RL( cvapor_exp, INDEX_NONE, 'cvapor_exp =',
138     & ' /* const. for Saturation calculation [?] */')
139     CALL WRITE_0D_RL( cvapor_fac_ice, INDEX_NONE, 'cvapor_fac_ice=',
140     & ' /* const. for Saturation calculation [?] */')
141     CALL WRITE_0D_RL( cvapor_exp_ice, INDEX_NONE, 'cvapor_exp_ice=',
142     & ' /* const. for Saturation calculation [?] */')
143     CALL WRITE_0D_RL( humid_fac, INDEX_NONE, 'humid_fac =',
144     & ' /* humidity coef. in virtual temp. [(kg/kg)^-1] */')
145     CALL WRITE_0D_RL( gamma_blk, INDEX_NONE, 'gamma_blk =',
146     & ' /* adiabatic lapse rate [?] */')
147     CALL WRITE_0D_RL( saltsat, INDEX_NONE, 'saltsat =',
148     & ' /* reduction of Qsat over salty water [-] */')
149     CALL WRITE_0D_L( noNegativeEvap,INDEX_NONE,'noNegativeEvap =',
150     & ' /* prevent negative Evaporation */')
151     CALL WRITE_0D_RL( sstExtrapol, INDEX_NONE, 'sstExtrapol =',
152     & ' /* extrapolation coeff from lev. 1 & 2 to surf [-] */')
153     CALL WRITE_0D_RL( cdrag_1, INDEX_NONE, 'cDrag_1 =',
154     & ' /* coef used in drag calculation [?] */')
155     CALL WRITE_0D_RL( cdrag_2, INDEX_NONE, 'cDrag_2 =',
156     & ' /* coef used in drag calculation [?] */')
157     CALL WRITE_0D_RL( cdrag_3, INDEX_NONE, 'cDrag_3 =',
158     & ' /* coef used in drag calculation [?] */')
159     CALL WRITE_0D_RL( cstanton_1, INDEX_NONE, 'cStanton_1 =',
160     & ' /* coef used in Stanton number calculation [?] */')
161     CALL WRITE_0D_RL( cstanton_2, INDEX_NONE, 'cStanton_2 =',
162     & ' /* coef used in Stanton number calculation [?] */')
163     CALL WRITE_0D_RL( cdalton, INDEX_NONE, 'cDalton =',
164     & ' /* coef used in Dalton number calculation [?] */')
165     CALL WRITE_0D_RL( exf_scal_BulkCdn, INDEX_NONE,
166     & 'exf_scal_BulkCdn=',
167     & ' /* Drag coefficient scaling factor [-] */')
168     CALL WRITE_0D_RL( zolmin, INDEX_NONE, 'zolmin =',
169     & ' /* minimum stability parameter [?] */')
170     CALL WRITE_0D_RL( psim_fac, INDEX_NONE, 'psim_fac =',
171     & ' /* coef used in turbulent fluxes calculation [-] */')
172     CALL WRITE_0D_RL( zref, INDEX_NONE, 'zref =',
173     & ' /* reference height [ m ] */')
174     CALL WRITE_0D_RL( hu, INDEX_NONE, 'hu =',
175     & ' /* height of mean wind [ m ] */')
176     CALL WRITE_0D_RL( ht, INDEX_NONE, 'ht =',
177     & ' /* height of mean temperature [ m ] */')
178     CALL WRITE_0D_RL( hq, INDEX_NONE, 'hq =',
179     & ' /* height of mean spec.humidity [ m ] */')
180     CALL WRITE_0D_RL( umin, INDEX_NONE, 'uMin =',
181     & ' /* minimum wind speed [m/s] */')
182     CALL WRITE_0D_L( useStabilityFct_overIce, INDEX_NONE,
183     & 'useStabilityFct_overIce=',
184     & ' /* transfert Coeffs over sea-ice depend on stability */')
185     CALL WRITE_0D_RL( exf_iceCd, INDEX_NONE, 'exf_iceCd =',
186     & ' /* drag coefficient over sea-ice (fixed) [-] */')
187     CALL WRITE_0D_RL( exf_iceCe, INDEX_NONE, 'exf_iceCe =',
188     & ' /* transfert coeff. over sea-ice, for Evap (fixed) [-] */')
189     CALL WRITE_0D_RL( exf_iceCh, INDEX_NONE, 'exf_iceCh =',
190     & ' /* transfert coeff. over sea-ice, Sens.Heat.(fixed)[-] */')
191     CALL WRITE_0D_RL( exf_albedo, INDEX_NONE, 'exf_albedo =',
192     & ' /* Sea-water albedo [-] */')
193     CALL WRITE_0D_L( useExfZenAlbedo, INDEX_NONE, 'useExfZenAlbedo =',
194     & ' /* Sea-water albedo varies with zenith angle */')
195     CALL WRITE_0D_I( select_ZenAlbedo,INDEX_NONE,'select_ZenAlbedo =',
196     & ' /* Sea-water albedo computation method */')
197     CALL WRITE_0D_L( useExfZenIncoming, INDEX_NONE,
198     & 'useExfZenIncoming =',' /* compute incoming solar radiation */')
199     CALL WRITE_0D_RL( ocean_emissivity, INDEX_NONE,
200     & 'ocean_emissivity =',
201     & ' /* longwave ocean-surface emissivity [-] */')
202     CALL WRITE_0D_RL( ice_emissivity, INDEX_NONE,'ice_emissivity =',
203     & ' /* longwave seaice emissivity [-] */')
204     CALL WRITE_0D_RL(snow_emissivity, INDEX_NONE,'snow_emissivity =',
205     & ' /* longwave snow emissivity [-] */')
206     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
207     & SQUEEZE_RIGHT , myThid )
208    
209     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
210     C-- Print settings of some CPP flags.
211     WRITE(msgBuf,'(A)') ' EXF main CPP flags:'
212     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
213     & SQUEEZE_RIGHT , myThid )
214     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
215     & SQUEEZE_RIGHT , myThid )
216    
217     #ifdef USE_EXF_INTERPOLATION
218     WRITE(msgBuf,'(A)')
219     &'// USE_EXF_INTERPOLATION: defined'
220     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
221     & SQUEEZE_RIGHT , myThid)
222     #else
223     WRITE(msgBuf,'(A)')
224     &'// USE_EXF_INTERPOLATION: NOT defined'
225     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
226     & SQUEEZE_RIGHT , myThid)
227     #endif
228    
229     #ifdef ALLOW_ATM_TEMP
230     WRITE(msgBuf,'(A)')
231     &'// ALLOW_ATM_TEMP: defined'
232     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
233     & SQUEEZE_RIGHT, myThid )
234     #else
235     WRITE(msgBuf,'(A)')
236     &'// ALLOW_ATM_TEMP: NOT defined'
237     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
238     & SQUEEZE_RIGHT, myThid )
239     #endif
240    
241     IF ( useAtmWind ) THEN
242     WRITE(msgBuf,'(A)')
243     &'// ALLOW_ATM_WIND (useAtmWind): defined'
244     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
245     & SQUEEZE_RIGHT, myThid )
246     ELSE
247     WRITE(msgBuf,'(A)')
248     &'// ALLOW_ATM_WIND (useAtmWind): NOT defined'
249     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
250     & SQUEEZE_RIGHT, myThid )
251     ENDIF
252    
253     #ifdef ALLOW_DOWNWARD_RADIATION
254     WRITE(msgBuf,'(A)')
255     &'// ALLOW_DOWNWARD_RADIATION: defined'
256     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
257     & SQUEEZE_RIGHT, myThid )
258     #else
259     WRITE(msgBuf,'(A)')
260     &'// ALLOW_DOWNWARD_RADIATION: NOT defined'
261     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
262     & SQUEEZE_RIGHT, myThid )
263     #endif
264    
265     #ifdef ALLOW_BULKFORMULAE
266     WRITE(msgBuf,'(A)')
267     &'// ALLOW_BULKFORMULAE: defined'
268     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
269     & SQUEEZE_RIGHT, myThid )
270     #else
271     WRITE(msgBuf,'(A)')
272     &'// ALLOW_BULKFORMULAE: NOT defined'
273     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
274     & SQUEEZE_RIGHT, myThid )
275     #endif
276    
277     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
278    
279     C-- For each data set used the summary prints the calendar data
280     C and the corresponding file from which the data will be read.
281     prtBlkLn = .FALSE.
282     addBlkLn = .TRUE.
283    
284     C-- Zonal wind stress.
285     IF ( .NOT.useAtmWind .AND. ustressfile.NE.' ' ) THEN
286     CALL EXF_FLD_SUMMARY( 'Zonal wind stress forcing',
287     I ustressfile, ustressRepCycle, ustressperiod,
288     I ustressStartTime, useExfYearlyFields, addBlkLn, myThid )
289     #ifdef USE_EXF_INTERPOLATION
290     CALL EXF_PRINT_INTERP( 'ustress',
291     & ustress_lon0, ustress_lon_inc, ustress_lat0, ustress_lat_inc,
292     & ustress_nlon, ustress_nlat, ustress_interpMethod, myThid )
293     #endif
294     prtBlkLn = .TRUE.
295     ENDIF
296    
297     C-- Meridional wind stress.
298     IF ( .NOT.useAtmWind .AND. vstressfile.NE.' ' ) THEN
299     CALL EXF_FLD_SUMMARY( 'Meridional wind stress forcing',
300     I vstressfile, vstressRepCycle, vstressperiod,
301     I vstressStartTime, useExfYearlyFields, addBlkLn, myThid )
302     #ifdef USE_EXF_INTERPOLATION
303     CALL EXF_PRINT_INTERP( 'vstress',
304     & vstress_lon0, vstress_lon_inc, vstress_lat0, vstress_lat_inc,
305     & vstress_nlon, vstress_nlat, vstress_interpMethod, myThid )
306     WRITE(msgBuf,'(2A,L5)') ' Interp. U & V comp. together:',
307     & ' uvInterp_stress =', uvInterp_stress
308     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
309     & SQUEEZE_RIGHT, myThid )
310     #endif
311     prtBlkLn = .TRUE.
312     ENDIF
313    
314     C-- Heat flux.
315     IF ( hfluxfile.NE.' ' ) THEN
316     CALL EXF_FLD_SUMMARY( 'Heat flux forcing',
317     I hfluxfile, hfluxRepCycle, hfluxperiod,
318     I hfluxStartTime, useExfYearlyFields, addBlkLn, myThid )
319     #ifdef USE_EXF_INTERPOLATION
320     CALL EXF_PRINT_INTERP( 'hflux',
321     & hflux_lon0, hflux_lon_inc, hflux_lat0, hflux_lat_inc,
322     & hflux_nlon, hflux_nlat, hflux_interpMethod, myThid )
323     #endif
324     prtBlkLn = .TRUE.
325     ENDIF
326    
327     C-- Fresh-Water flux.
328     IF ( sfluxfile.NE.' ' ) THEN
329     CALL EXF_FLD_SUMMARY( 'Fresh-Water flux forcing',
330     I sfluxfile, sfluxRepCycle, sfluxperiod,
331     I sfluxStartTime, useExfYearlyFields, addBlkLn, myThid )
332     #ifdef USE_EXF_INTERPOLATION
333     CALL EXF_PRINT_INTERP( 'sflux',
334     & sflux_lon0, sflux_lon_inc, sflux_lat0, sflux_lat_inc,
335     & sflux_nlon, sflux_nlat, sflux_interpMethod, myThid )
336     #endif
337     prtBlkLn = .TRUE.
338     ENDIF
339    
340     #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
341     C-- Net shortwave.
342     IF ( swfluxfile.NE.' ' ) THEN
343     CALL EXF_FLD_SUMMARY( 'Net shortwave flux forcing',
344     I swfluxfile, swfluxRepCycle, swfluxperiod,
345     I swfluxStartTime, useExfYearlyFields, addBlkLn, myThid )
346     #ifdef USE_EXF_INTERPOLATION
347     CALL EXF_PRINT_INTERP( 'swflux',
348     & swflux_lon0, swflux_lon_inc, swflux_lat0, swflux_lat_inc,
349     & swflux_nlon, swflux_nlat, swflux_interpMethod, myThid )
350     #endif
351     prtBlkLn = .TRUE.
352     ENDIF
353     #endif /* ALLOW_ATM_TEMP or SHORTWAVE_HEATING */
354    
355     C-- Zonal wind.
356     IF ( useAtmWind .AND. uwindfile.NE.' ' ) THEN
357     CALL EXF_FLD_SUMMARY( 'Zonal wind forcing',
358     I uwindfile, uwindRepCycle, uwindperiod,
359     I uwindStartTime, useExfYearlyFields, addBlkLn, myThid )
360     #ifdef USE_EXF_INTERPOLATION
361     CALL EXF_PRINT_INTERP( 'uwind',
362     & uwind_lon0, uwind_lon_inc, uwind_lat0, uwind_lat_inc,
363     & uwind_nlon, uwind_nlat, uwind_interpMethod, myThid )
364     #endif
365     prtBlkLn = .TRUE.
366     ENDIF
367    
368     C-- Meridional wind.
369     IF ( useAtmWind .AND. vwindfile.NE.' ' ) THEN
370     CALL EXF_FLD_SUMMARY( 'Meridional wind forcing',
371     I vwindfile, vwindRepCycle, vwindperiod,
372     I vwindStartTime, useExfYearlyFields, addBlkLn, myThid )
373     #ifdef USE_EXF_INTERPOLATION
374     CALL EXF_PRINT_INTERP( 'vwind',
375     & vwind_lon0, vwind_lon_inc, vwind_lat0, vwind_lat_inc,
376     & vwind_nlon, vwind_nlat, vwind_interpMethod, myThid )
377     WRITE(msgBuf,'(2A,L5)') ' Interp. U & V comp. together:',
378     & ' uvInterp_wind =', uvInterp_wind
379     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
380     & SQUEEZE_RIGHT, myThid )
381     #endif
382     prtBlkLn = .TRUE.
383     ENDIF
384    
385     C-- Surface wind speed
386     IF ( wspeedfile.NE.' ' ) THEN
387     CALL EXF_FLD_SUMMARY( 'Surface wind speed',
388     I wspeedfile, wspeedRepCycle, wspeedperiod,
389     I wspeedStartTime, useExfYearlyFields, addBlkLn, myThid )
390     #ifdef USE_EXF_INTERPOLATION
391     CALL EXF_PRINT_INTERP( 'wspeed',
392     & wspeed_lon0, wspeed_lon_inc, wspeed_lat0, wspeed_lat_inc,
393     & wspeed_nlon, wspeed_nlat, wspeed_interpMethod, myThid )
394     #endif
395     prtBlkLn = .TRUE.
396     ENDIF
397    
398     #ifdef ALLOW_ATM_TEMP
399     C-- Atmospheric temperature.
400     IF ( atempfile.NE.' ' ) THEN
401     CALL EXF_FLD_SUMMARY( 'Atmospheric temperature',
402     I atempfile, atempRepCycle, atempperiod,
403     I atempStartTime, useExfYearlyFields, addBlkLn, myThid )
404     #ifdef USE_EXF_INTERPOLATION
405     CALL EXF_PRINT_INTERP( 'atemp',
406     & atemp_lon0, atemp_lon_inc, atemp_lat0, atemp_lat_inc,
407     & atemp_nlon, atemp_nlat, atemp_interpMethod, myThid )
408     #endif
409     prtBlkLn = .TRUE.
410     ENDIF
411    
412     C-- Atmospheric specific humidity.
413     IF ( aqhfile.NE.' ' ) THEN
414     CALL EXF_FLD_SUMMARY( 'Atmospheric specific humidity',
415     I aqhfile, aqhRepCycle, aqhperiod,
416     I aqhStartTime, useExfYearlyFields, addBlkLn, myThid )
417     #ifdef USE_EXF_INTERPOLATION
418     CALL EXF_PRINT_INTERP( 'aqh',
419     & aqh_lon0, aqh_lon_inc, aqh_lat0, aqh_lat_inc,
420     & aqh_nlon, aqh_nlat, aqh_interpMethod, myThid )
421     #endif
422     prtBlkLn = .TRUE.
423     ENDIF
424    
425     C-- Turbulent heat flues
426     IF ( prtBlkLn ) THEN
427     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
428     & SQUEEZE_RIGHT, myThid )
429     prtBlkLn = .FALSE.
430     ENDIF
431     #ifdef ALLOW_READ_TURBFLUXES
432     WRITE(msgBuf,'(A)')
433     &'// ALLOW_READ_TURBFLUXES: defined'
434     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
435     & SQUEEZE_RIGHT, myThid )
436    
437     C-- Sensible heat flux
438     IF ( hs_file.NE.' ' ) THEN
439     CALL EXF_FLD_SUMMARY( 'Sensible heat flux (+=down)',
440     I hs_file, hs_RepCycle, hs_period,
441     I hs_StartTime, useExfYearlyFields, addBlkLn, myThid )
442     #ifdef USE_EXF_INTERPOLATION
443     CALL EXF_PRINT_INTERP( 'hs',
444     & hs_lon0, hs_lon_inc, hs_lat0, hs_lat_inc,
445     & hs_nlon, hs_nlat, hs_interpMethod, myThid )
446     #endif
447     prtBlkLn = .TRUE.
448     ENDIF
449    
450     C-- Latent heat flux
451     IF ( hl_file.NE.' ' ) THEN
452     CALL EXF_FLD_SUMMARY( 'Latent heat flux (+=down)',
453     I hl_file, hl_RepCycle, hl_period,
454     I hl_StartTime, useExfYearlyFields, addBlkLn, myThid )
455     #ifdef USE_EXF_INTERPOLATION
456     CALL EXF_PRINT_INTERP( 'hl',
457     & hl_lon0, hl_lon_inc, hl_lat0, hl_lat_inc,
458     & hl_nlon, hl_nlat, hl_interpMethod, myThid )
459     #endif
460     prtBlkLn = .TRUE.
461     ENDIF
462    
463     #else /* ALLOW_READ_TURBFLUXES */
464     WRITE(msgBuf,'(A)')
465     &'// ALLOW_READ_TURBFLUXES: NOT defined'
466     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
467     & SQUEEZE_RIGHT, myThid )
468     #endif /* ALLOW_READ_TURBFLUXES */
469    
470     C-- Net longwave.
471     IF ( lwfluxfile.NE.' ' ) THEN
472     CALL EXF_FLD_SUMMARY( 'Net longwave flux forcing',
473     I lwfluxfile, lwfluxRepCycle, lwfluxperiod,
474     I lwfluxStartTime, useExfYearlyFields, addBlkLn, myThid )
475     #ifdef USE_EXF_INTERPOLATION
476     CALL EXF_PRINT_INTERP( 'lwflux',
477     & lwflux_lon0, lwflux_lon_inc, lwflux_lat0, lwflux_lat_inc,
478     & lwflux_nlon, lwflux_nlat, lwflux_interpMethod, myThid )
479     #endif
480     prtBlkLn = .TRUE.
481     ENDIF
482     #endif /* ALLOW_ATM_TEMP */
483    
484     C-- Evaporation.
485     IF ( prtBlkLn ) THEN
486     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
487     & SQUEEZE_RIGHT, myThid )
488     prtBlkLn = .FALSE.
489     ENDIF
490     #ifdef EXF_READ_EVAP
491     WRITE(msgBuf,'(A)')
492     &'// EXF_READ_EVAP: defined'
493     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
494     & SQUEEZE_RIGHT, myThid )
495     # ifdef ALLOW_ATM_TEMP
496     IF ( evapfile.NE.' ' ) THEN
497     addBlkLn = .FALSE.
498     CALL EXF_FLD_SUMMARY( 'Evaporation',
499     I evapfile, evapRepCycle, evapperiod,
500     I evapStartTime, useExfYearlyFields, addBlkLn, myThid )
501     addBlkLn = .TRUE.
502     #ifdef USE_EXF_INTERPOLATION
503     CALL EXF_PRINT_INTERP( 'evap',
504     & evap_lon0, evap_lon_inc, evap_lat0, evap_lat_inc,
505     & evap_nlon, evap_nlat, evap_interpMethod, myThid )
506     #endif
507     prtBlkLn = .TRUE.
508     ENDIF
509     # endif /* ALLOW_ATM_TEMP */
510     #else /* EXF_READ_EVAP */
511     WRITE(msgBuf,'(A)')
512     &'// EXF_READ_EVAP: NOT defined'
513     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
514     & SQUEEZE_RIGHT, myThid )
515     #endif /* EXF_READ_EVAP */
516    
517     #ifdef ALLOW_ATM_TEMP
518     C-- Precipitation.
519     IF ( precipfile.NE.' ' ) THEN
520     CALL EXF_FLD_SUMMARY( 'Precipitation data',
521     I precipfile, precipRepCycle, precipperiod,
522     I precipStartTime, useExfYearlyFields, addBlkLn, myThid )
523     #ifdef USE_EXF_INTERPOLATION
524     CALL EXF_PRINT_INTERP( 'precip',
525     & precip_lon0, precip_lon_inc, precip_lat0, precip_lat_inc,
526     & precip_nlon, precip_nlat, precip_interpMethod, myThid )
527     #endif
528     prtBlkLn = .TRUE.
529     ENDIF
530    
531     C-- Snow Precipitation
532     IF ( snowprecipfile.NE.' ' ) THEN
533     CALL EXF_FLD_SUMMARY( 'Snow Precipitation data',
534     I snowprecipfile, snowprecipRepCycle, snowprecipperiod,
535     I snowprecipStartTime, useExfYearlyFields, addBlkLn, myThid )
536     #ifdef USE_EXF_INTERPOLATION
537     CALL EXF_PRINT_INTERP( 'snowprecip',
538     & snowprecip_lon0, snowprecip_lon_inc, snowprecip_lat0,
539     & snowprecip_lat_inc, snowprecip_nlon, snowprecip_nlat,
540     & snowprecip_interpMethod, myThid )
541     #endif
542     prtBlkLn = .TRUE.
543     ENDIF
544     #endif /* ALLOW_ATM_TEMP */
545    
546     C-- Runoff.
547     IF ( prtBlkLn ) THEN
548     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
549     & SQUEEZE_RIGHT, myThid )
550     prtBlkLn = .FALSE.
551     ENDIF
552     #ifdef ALLOW_RUNOFF
553     WRITE(msgBuf,'(A)')
554     &'// ALLOW_RUNOFF: defined'
555     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
556     & SQUEEZE_RIGHT, myThid )
557     IF ( runofffile.NE.' ' ) THEN
558     addBlkLn = .FALSE.
559     CALL EXF_FLD_SUMMARY( 'Runoff data',
560     I runofffile, runoffRepCycle, runoffperiod,
561     I runoffStartTime, useExfYearlyFields, addBlkLn, myThid )
562     addBlkLn = .TRUE.
563     # ifdef USE_EXF_INTERPOLATION
564     CALL EXF_PRINT_INTERP( 'runoff',
565     & runoff_lon0, runoff_lon_inc, runoff_lat0, runoff_lat_inc,
566     & runoff_nlon, runoff_nlat, runoff_interpMethod, myThid )
567     # endif /* USE_EXF_INTERPOLATION */
568     prtBlkLn = .TRUE.
569     ENDIF
570     IF ( prtBlkLn ) THEN
571     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
572     & SQUEEZE_RIGHT, myThid )
573     prtBlkLn = .FALSE.
574     ENDIF
575     # ifdef ALLOW_RUNOFTEMP
576     WRITE(msgBuf,'(A)')
577     &'// ALLOW_RUNOFTEMP: defined'
578     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
579     & SQUEEZE_RIGHT, myThid )
580     IF ( runoftempfile.NE.' ' ) THEN
581     c addBlkLn = .FALSE.
582     c CALL EXF_FLD_SUMMARY( 'Runoff temp.',
583     c I runoftempfile, runoffRepCycle, runoffperiod,
584     c I runoffStartTime, useExfYearlyFields, addBlkLn, myThid )
585     c addBlkLn = .TRUE.
586     il = ILNBLNK(runoftempfile)
587     WRITE(msgBuf,'(A)')
588     & ' Runoff temp. is read from file:'
589     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
590     & SQUEEZE_RIGHT, myThid )
591     WRITE(msgBuf,'(3A)') ' >> ', runoftempfile(1:il), ' <<'
592     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
593     & SQUEEZE_RIGHT, myThid )
594     prtBlkLn = .TRUE.
595     ENDIF
596     # else /* ALLOW_RUNOFTEMP */
597     WRITE(msgBuf,'(A)')
598     &'// ALLOW_RUNOFTEMP: NOT defined'
599     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
600     & SQUEEZE_RIGHT, myThid )
601     # endif /* ALLOW_RUNOFTEMP */
602     #else /* ALLOW_RUNOFF */
603     WRITE(msgBuf,'(A)')
604     &'// ALLOW_RUNOFF: NOT defined'
605     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
606     & SQUEEZE_RIGHT, myThid )
607     #endif /* ALLOW_RUNOFF */
608    
609     C-- Salt-Flux
610     IF ( prtBlkLn ) THEN
611     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
612     & SQUEEZE_RIGHT, myThid )
613     prtBlkLn = .FALSE.
614     ENDIF
615     #ifdef ALLOW_SALTFLX
616     WRITE(msgBuf,'(A)')
617     &'// ALLOW_SALTFLX: defined'
618     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
619     & SQUEEZE_RIGHT, myThid )
620     IF ( saltflxfile.NE.' ' ) THEN
621     CALL EXF_FLD_SUMMARY( 'Net upward Salt-Flux forcing',
622     I saltflxfile, saltflxRepCycle, saltflxperiod,
623     I saltflxStartTime, useExfYearlyFields, addBlkLn, myThid )
624     #ifdef USE_EXF_INTERPOLATION
625     CALL EXF_PRINT_INTERP( 'saltflx',
626     & saltflx_lon0, saltflx_lon_inc, saltflx_lat0, saltflx_lat_inc,
627     & saltflx_nlon, saltflx_nlat, saltflx_interpMethod, myThid )
628     #endif
629     prtBlkLn = .TRUE.
630     ENDIF
631     #else /* ALLOW_SALTFLX */
632     WRITE(msgBuf,'(A)')
633     &'// ALLOW_SALTFLX: NOT defined'
634     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
635     & SQUEEZE_RIGHT, myThid )
636     #endif /* ALLOW_SALTFLX */
637    
638     #ifdef ALLOW_DOWNWARD_RADIATION
639     C-- Downward shortwave.
640     IF ( swdownfile.NE.' ' ) THEN
641     CALL EXF_FLD_SUMMARY( 'Downward shortwave flux',
642     I swdownfile, swdownRepCycle, swdownperiod,
643     I swdownStartTime, useExfYearlyFields, addBlkLn, myThid )
644     #ifdef USE_EXF_INTERPOLATION
645     CALL EXF_PRINT_INTERP( 'swdown',
646     & swdown_lon0, swdown_lon_inc, swdown_lat0, swdown_lat_inc,
647     & swdown_nlon, swdown_nlat, swdown_interpMethod, myThid )
648     #endif
649     prtBlkLn = .TRUE.
650     ENDIF
651    
652     C-- Downward longwave.
653     IF ( lwdownfile.NE.' ' ) THEN
654     CALL EXF_FLD_SUMMARY( 'Downward longwave flux',
655     I lwdownfile, lwdownRepCycle, lwdownperiod,
656     I lwdownStartTime, useExfYearlyFields, addBlkLn, myThid )
657     #ifdef USE_EXF_INTERPOLATION
658     CALL EXF_PRINT_INTERP( 'lwdown',
659     & lwdown_lon0, lwdown_lon_inc, lwdown_lat0, lwdown_lat_inc,
660     & lwdown_nlon, lwdown_nlat, lwdown_interpMethod, myThid )
661     #endif
662     prtBlkLn = .TRUE.
663     ENDIF
664     #endif /* ALLOW_DOWNWARD_RADIATION */
665    
666     #ifdef ATMOSPHERIC_LOADING
667     C-- Atmospheric pressure.
668     IF ( apressurefile.NE.' ' ) THEN
669     CALL EXF_FLD_SUMMARY( 'Atmospheric pressure forcing',
670     I apressurefile, apressureRepCycle, apressureperiod,
671     I apressureStartTime, useExfYearlyFields, addBlkLn, myThid )
672     #ifdef USE_EXF_INTERPOLATION
673     CALL EXF_PRINT_INTERP( 'apressure', apressure_lon0,
674     & apressure_lon_inc, apressure_lat0, apressure_lat_inc,
675     & apressure_nlon, apressure_nlat, apressure_interpMethod, myThid )
676     #endif
677     prtBlkLn = .TRUE.
678     ENDIF
679     #endif /* ATMOSPHERIC_LOADING */
680    
681     #ifdef EXF_ALLOW_TIDES
682     C-- Tidal geopotential
683     IF ( tidePotFile.NE.' ' ) THEN
684     CALL EXF_FLD_SUMMARY( 'Tidal geopotential',
685     I tidePotFile, tidePotRepCycle, tidePotPeriod,
686     I tidePotStartTime, useExfYearlyFields, addBlkLn, myThid )
687     #ifdef USE_EXF_INTERPOLATION
688     CALL EXF_PRINT_INTERP( 'tidePot', tidePot_lon0,
689     & tidePot_lon_inc, tidePot_lat0, tidePot_lat_inc,
690     & tidePot_nlon, tidePot_nlat, tidePot_interpMethod, myThid )
691     #endif
692     prtBlkLn = .TRUE.
693     ENDIF
694     #endif /* EXF_ALLOW_TIDES */
695    
696     #ifdef EXF_SEAICE_FRACTION
697     C-- Fractional ice-covered area
698     IF ( areamaskfile.NE.' ' ) THEN
699     CALL EXF_FLD_SUMMARY( 'Fractional ice-covered area',
700     I areamaskfile, areamaskRepCycle, areamaskperiod,
701     I areamaskStartTime, useExfYearlyFields, addBlkLn, myThid )
702     #ifdef USE_EXF_INTERPOLATION
703     CALL EXF_PRINT_INTERP( 'areamask', areamask_lon0,
704     & areamask_lon_inc, areamask_lat0, areamask_lat_inc,
705     & areamask_nlon, areamask_nlat, areamask_interpMethod, myThid )
706     #endif
707     prtBlkLn = .TRUE.
708     ENDIF
709     #endif /* EXF_SEAICE_FRACTION */
710    
711     C-- Atmospheric pCO2
712     il = ilnblnk(apco2file)
713     write(msgbuf,'(a)') ' '
714     call print_message( msgbuf, standardmessageunit,
715     & SQUEEZE_RIGHT , mythid)
716     write(msgbuf,'(a,f12.0)')
717     &' Atmospheric pCO2 forcing period is ',
718     & apco2period
719     call print_message( msgbuf, standardmessageunit,
720     & SQUEEZE_RIGHT , mythid)
721     write(msgbuf,'(a)')
722     &' Atmospheric pCO2 forcing is read from file:'
723     call print_message( msgbuf, standardmessageunit,
724     & SQUEEZE_RIGHT , mythid)
725     write(msgbuf,'(a,a,a)')
726     &' >> ',apco2file(1:il),' <<'
727     call print_message( msgbuf, standardmessageunit,
728     & SQUEEZE_RIGHT , mythid)
729    
730     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
731    
732     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
733     & SQUEEZE_RIGHT, myThid )
734     WRITE(msgBuf,'(A)')
735     &'// ======================================================='
736     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
737     & SQUEEZE_RIGHT, myThid )
738     WRITE(msgBuf,'(A)')
739     &'// External forcing (EXF) climatology configuration :'
740     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
741     & SQUEEZE_RIGHT, myThid )
742     WRITE(msgBuf,'(A)')
743     &'// ======================================================='
744     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
745     & SQUEEZE_RIGHT, myThid )
746     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
747     & SQUEEZE_RIGHT, myThid )
748     prtBlkLn = .FALSE.
749     addBlkLn = .FALSE.
750    
751     C For each data set used the summary prints the calendar data
752     C and the corresponding file from which the data will be read.
753    
754     C The climatological data sets are assumed to contain monthly
755     C data. This can be changed in a later version to an arbitrary
756     C number of intervals during a given year.
757    
758     #ifdef ALLOW_CLIMSST_RELAXATION
759     WRITE(msgBuf,'(A)')
760     &'// ALLOW_CLIMSST_RELAXATION: defined'
761     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
762     & SQUEEZE_RIGHT, myThid )
763     C Relaxation to SST climatology.
764     IF ( climsstfile .NE. ' ' ) THEN
765     CALL EXF_FLD_SUMMARY( 'Climatological SST',
766     I climsstfile, climsstRepCycle, climsstperiod,
767     I climsstStartTime, useExfYearlyFields, addBlkLn, myThid )
768     #ifdef USE_EXF_INTERPOLATION
769     CALL EXF_PRINT_INTERP( 'climsst',
770     & climsst_lon0, climsst_lon_inc, climsst_lat0, climsst_lat_inc,
771     & climsst_nlon, climsst_nlat, climsst_interpMethod, myThid )
772     #endif
773     prtBlkLn = .TRUE.
774     ELSE
775     WRITE(msgBuf,'(A)') ' climsst relaxation is NOT used'
776     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
777     & SQUEEZE_RIGHT, myThid )
778     ENDIF
779     #else /* ALLOW_CLIMSST_RELAXATION */
780     WRITE(msgBuf,'(A)')
781     &'// ALLOW_CLIMSST_RELAXATION: NOT defined'
782     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
783     & SQUEEZE_RIGHT, myThid )
784     #endif /* ALLOW_CLIMSST_RELAXATION */
785    
786     c IF ( prtBlkLn ) THEN
787     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
788     & SQUEEZE_RIGHT, myThid )
789     c prtBlkLn = .FALSE.
790     c ENDIF
791    
792     #ifdef ALLOW_CLIMSSS_RELAXATION
793     WRITE(msgBuf,'(A)')
794     &'// ALLOW_CLIMSSS_RELAXATION: defined'
795     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
796     & SQUEEZE_RIGHT, myThid )
797     C Relaxation to SSS climatology.
798     IF ( climsssfile .NE. ' ' ) THEN
799     CALL EXF_FLD_SUMMARY( 'Climatological SSS',
800     I climsssfile, climsssRepCycle, climsssperiod,
801     I climsssStartTime, useExfYearlyFields, addBlkLn, myThid )
802     #ifdef USE_EXF_INTERPOLATION
803     CALL EXF_PRINT_INTERP( 'climsss',
804     & climsss_lon0, climsss_lon_inc, climsss_lat0, climsss_lat_inc,
805     & climsss_nlon, climsss_nlat, climsss_interpMethod, myThid )
806     #endif
807     prtBlkLn = .TRUE.
808     ELSE
809     WRITE(msgBuf,'(A)') ' climsss relaxation is NOT used'
810     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
811     & SQUEEZE_RIGHT, myThid )
812     ENDIF
813     #else /* ALLOW_CLIMSSS_RELAXATION */
814     WRITE(msgBuf,'(A)')
815     &'// ALLOW_CLIMSSS_RELAXATION: NOT defined'
816     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
817     & SQUEEZE_RIGHT, myThid )
818     #endif /* ALLOW_CLIMSSS_RELAXATION */
819    
820     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
821     & SQUEEZE_RIGHT, myThid )
822     WRITE(msgBuf,'(A)')
823     &'// ======================================================='
824     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
825     & SQUEEZE_RIGHT, myThid )
826     WRITE(msgBuf,'(A)')
827     &'// External forcing (EXF) configuration >>> END <<<'
828     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
829     & SQUEEZE_RIGHT, myThid )
830     WRITE(msgBuf,'(A)')
831     &'// ======================================================='
832     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
833     & SQUEEZE_RIGHT, myThid )
834     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
835     & SQUEEZE_RIGHT, myThid )
836    
837     _END_MASTER( myThid )
838    
839     RETURN
840     END
841    
842     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
843     CBOP
844     C !ROUTINE: EXF_FLD_SUMMARY
845     C !INTERFACE:
846     SUBROUTINE EXF_FLD_SUMMARY(
847     I fld_fullName, fld_file,
848     I fld_repeatCycle, fld_period, fld_start_time,
849     I useYearlyFields, addBlkLn, myThid )
850    
851     C !DESCRIPTION:
852     C Print EXF timing parameters for one EXF input field
853    
854     C !USES:
855     IMPLICIT NONE
856    
857     #include "EEPARAMS.h"
858    
859     C !INPUT PARAMETERS:
860     C fld_fullName :: field full name description (shorter than 32c)
861     C fld_file :: file-name for this field
862     C fld_repeatCycle :: time duration of a repeating cycle
863     C fld_period :: time period (in sec) between 2 reccords
864     C fld_start_time :: corresponding starting time (in sec) for this field
865     C useYearlyFields :: select if using EXF Yearly-fields or not
866     C addBlkLn :: print blank line before parameter summary
867     C myThid :: My Thread Id number
868     CHARACTER*(*) fld_fullName
869     CHARACTER*(*) fld_file
870     _RL fld_repeatCycle
871     _RL fld_period
872     _RL fld_start_time
873     LOGICAL useYearlyFields
874     LOGICAL addBlkLn
875     INTEGER myThid
876    
877     C !FUNCTIONS:
878     INTEGER ILNBLNK
879     EXTERNAL ILNBLNK
880    
881     C !LOCAL VARIABLES:
882     INTEGER iL, jL
883     CHARACTER*(MAX_LEN_MBUF) tmpBuf, msgBuf
884     CHARACTER*1 blkLin
885     CEOP
886    
887     blkLin = ' '
888     jL = 47
889    
890     IF ( addBlkLn ) THEN
891     CALL PRINT_MESSAGE( blkLin, standardMessageUnit,
892     & SQUEEZE_RIGHT, myThid )
893     ENDIF
894     IF ( fld_period.GT.0. ) THEN
895     WRITE(tmpBuf,'(3A)') ' ', fld_fullName, ' starts at'
896     WRITE(msgBuf,'(A,F12.0)') tmpBuf(1:jL), fld_start_time
897     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
898     & SQUEEZE_RIGHT, myThid )
899     ENDIF
900     WRITE(tmpBuf,'(3A)') ' ', fld_fullName, ' period is'
901     WRITE(msgBuf,'(A,F12.0)') tmpBuf(1:jL), fld_period
902     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
903     & SQUEEZE_RIGHT, myThid )
904     c IF ( fld_period.GT.0. .AND. .NOT.useYearlyFields ) THEN
905     IF ( fld_period.GT.0. ) THEN
906     iL = ILNBLNK(fld_fullName)
907     IF ( iL.LT.28 ) THEN
908     WRITE(tmpBuf,'(3A)') ' ', fld_fullName, ' repeat-cycle is'
909     ELSE
910     WRITE(tmpBuf,'(3A)') ' ', fld_fullName, ' rep-cycle is'
911     ENDIF
912     WRITE(msgBuf,'(A,F12.0)') tmpBuf(1:jL), fld_repeatCycle
913     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
914     & SQUEEZE_RIGHT, myThid )
915     ENDIF
916     WRITE(msgBuf,'(3A)') ' ', fld_fullName, ' is read from file:'
917     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
918     & SQUEEZE_RIGHT, myThid )
919     iL = ILNBLNK(fld_file)
920     WRITE(msgBuf,'(3A)') ' >> ', fld_file(1:iL), ' <<'
921     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
922     & SQUEEZE_RIGHT, myThid )
923    
924     RETURN
925     END
926    
927     #ifdef USE_EXF_INTERPOLATION
928     C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
929     CBOP
930     C !ROUTINE: EXF_PRINT_INTERP
931     C !INTERFACE:
932     SUBROUTINE EXF_PRINT_INTERP( var_name,
933     I var_lon0, var_lon_inc, var_lat0, var_lat_inc,
934     I var_nlon, var_nlat, var_interpMethod, myThid )
935    
936     C !DESCRIPTION:
937     C Print EXF interpolation parameters for one EXF input field
938    
939     C !USES:
940     IMPLICIT NONE
941    
942     #include "EEPARAMS.h"
943    
944     C !INPUT PARAMETERS:
945     C myThid :: My Thread Id number
946     CHARACTER*(*) var_name
947     _RL var_lon0, var_lon_inc, var_lat0
948     _RL var_lat_inc(*)
949     INTEGER var_nlon, var_nlat, var_interpMethod
950     INTEGER myThid
951    
952     C !FUNCTIONS:
953     c INTEGER ILNBLNK
954     c EXTERNAL ILNBLNK
955    
956     C !LOCAL VARIABLES:
957     INTEGER i
958     _RL var_min, var_max
959     CHARACTER*(MAX_LEN_MBUF) msgBuf
960     CEOP
961    
962     IF ( var_interpMethod.EQ.0 ) THEN
963     WRITE(msgBuf,'(3X,A,A,A)')
964     & 'assume "',var_name,'" on model-grid (no interpolation)'
965     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
966     & SQUEEZE_RIGHT , myThid )
967     ELSE
968     WRITE(msgBuf,'(3X,A,A,A,I3,A)')
969     & 'interpolate "',var_name,'" (method=',var_interpMethod,' ):'
970     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
971     & SQUEEZE_RIGHT , myThid )
972     C- print input-field longitude position:
973     IF ( ABS(var_lon0).LT.1000. .AND. var_lon_inc.GT.-10.
974     & .AND. var_lon_inc.LT.100. ) THEN
975     WRITE(msgBuf,'(3X,A,F10.5,A,I6,A,F10.7)')
976     & 'lon0=', var_lon0, ', nlon=', var_nlon,
977     & ', lon_inc=',var_lon_inc
978     ELSE
979     WRITE(msgBuf,'(3X,A,1PE10.3,A,I6,A,1PE10.3)')
980     & 'lon0=', var_lon0, ', nlon=', var_nlon,
981     & ', lon_inc=',var_lon_inc
982     ENDIF
983     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
984     & SQUEEZE_RIGHT , myThid )
985     C- print input-field latitude position:
986     var_min = var_lat_inc(1)
987     var_max = var_lat_inc(1)
988     DO i=1,var_nlat-1
989     var_min = MIN( var_lat_inc(i), var_min )
990     var_max = MAX( var_lat_inc(i), var_max )
991     ENDDO
992     IF ( ABS(var_lat0).LT.1000. .AND. var_min.GT.-10.
993     & .AND. var_max.LT.100. ) THEN
994     IF ( var_min.EQ.var_max ) THEN
995     WRITE(msgBuf,'(3X,A,F10.5,A,I6,A,F10.7)')
996     & 'lat0=', var_lat0, ', nlat=', var_nlat,
997     & ', lat_inc=', var_min
998     ELSE
999     WRITE(msgBuf,'(3X,A,F10.5,A,I6,A,2F8.5)')
1000     & 'lat0=', var_lat0, ', nlat=', var_nlat,
1001     & ', inc(min,max)=', var_min, var_max
1002     ENDIF
1003     ELSE
1004     IF ( var_min.EQ.var_max ) THEN
1005     WRITE(msgBuf,'(3X,A,1PE10.3,A,I6,A,1PE10.3)')
1006     & 'lat0=', var_lat0, ', nlat=', var_nlat,
1007     & ', lat_inc=', var_min
1008     ELSE
1009     WRITE(msgBuf,'(3X,A,1PE10.3,A,I6,A,1P2E10.3)')
1010     & 'lat0=', var_lat0, ', nlat=', var_nlat,
1011     & ', inc(min,max)=', var_min, var_max
1012     ENDIF
1013     ENDIF
1014     CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
1015     & SQUEEZE_RIGHT , myThid )
1016     ENDIF
1017    
1018     RETURN
1019     END
1020     #endif /* USE_EXF_INTERPOLATION */

  ViewVC Help
Powered by ViewVC 1.1.22