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

Diff of /MITgcm/pkg/exf/exf_summary.F

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

revision 1.6 by edhill, Thu Oct 9 04:19:19 2003 UTC revision 1.16 by mlosch, Fri Feb 1 20:34:00 2008 UTC
# Line 1  Line 1 
1  c $Header$  C $Header$
2    C $Name$
3    
4  #include "EXF_OPTIONS.h"  #include "EXF_OPTIONS.h"
5    
6    
7        subroutine exf_Summary(        SUBROUTINE EXF_SUMMARY( myThid )
      I                        mythid  
      &                      )  
8    
9  c     ==================================================================  c     ==================================================================
10  c     SUBROUTINE exf_Summary  c     SUBROUTINE exf_summary
11  c     ==================================================================  c     ==================================================================
12  c  c
13  c     o List all the settings of the external forcing.  c     o List all the settings of the external forcing.
# Line 26  c     changed: Dimitris Menemenlis menem Line 25  c     changed: Dimitris Menemenlis menem
25  c              - modifications for using pkg/exf with pkg/seaice  c              - modifications for using pkg/exf with pkg/seaice
26  c  c
27  c     ==================================================================  c     ==================================================================
28  c     SUBROUTINE exf_Summary  c     SUBROUTINE exf_summary
29  c     ==================================================================  c     ==================================================================
30    
31        implicit none        implicit none
32    
33  c     == global variables ==  C     == global variables ==
34    
35  #include "EEPARAMS.h"  #include "EEPARAMS.h"
36  #include "SIZE.h"  #include "SIZE.h"
37  #include "cal.h"  #include "cal.h"
38  #include "exf.h"  #include "EXF_CONSTANTS.h"
39  #include "exf_param.h"  #include "EXF_PARAM.h"
40    
41  c     == routine arguments ==  C     == routine arguments ==
42    
43  c     mythid  - thread number for this instance of the routine.  C     myThid  - thread number for this instance of the routine.
44    
45        integer mythid        integer myThid
46    
47  c     == local variables ==  C     == local variables ==
48    
       integer i  
49        integer il        integer il
       integer timeint(4)  
50    
51        character*(max_len_mbuf) msgbuf        character*(max_len_mbuf) msgbuf
52    
53  c     == external ==  C     == external ==
54    
55        integer  ilnblnk        integer  ilnblnk
56        external ilnblnk        external ilnblnk
57    
58  c     == end of interface ==  C     == end of interface ==
59    
60        write(msgbuf,'(a)')        _BEGIN_MASTER( myThid )
61       &' '  
62          write(msgbuf,'(a)') ' '
63        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
64       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
65        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 76  c     == end of interface == Line 74  c     == end of interface ==
74       &'// ======================================================='       &'// ======================================================='
75        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
76       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
77        write(msgbuf,'(a)')        write(msgbuf,'(a)') ' '
      &' '  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a,a)')  
      &'External forcing version: ',externalforcingversion  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a,a)')  
      &'Uses Calendar version:    ',usescalendarversion  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a)')  
      &' '  
78        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
79       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
80    
81  c--   Print settings of some CPP flags.  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( useExfCheckRange, INDEX_NONE,
98         &  'useExfCheckRange =',
99         &  ' /* check for fields range */')
100          CALL WRITE_0D_R8( exf_monFreq, INDEX_NONE, 'exf_monFreq =',
101         &  ' /* EXF monitor frequency [ s ] */')
102          CALL WRITE_0D_R8( repeatPeriod, INDEX_NONE, 'repeatPeriod =',
103         &  ' /* period for cycling forcing dataset [ s ] */')
104          CALL WRITE_0D_R8( climtempfreeze, INDEX_NONE,'climTempFreeze=',
105         &  ' /* Minimum climatological temperature [deg.C] */')
106          CALL WRITE_0D_R8( windStressMax, INDEX_NONE,'windStressMax =',
107         &  ' /* Maximum absolute windstress [ Pa ] */')
108          CALL WRITE_0D_L( stressIsOnCgrid,INDEX_NONE,'stressIsOnCgrid =',
109         &  ' /* set u,v_stress on Arakawa C-grid */')
110          CALL WRITE_0D_R8( cen2kel, INDEX_NONE, 'cen2kel =',
111         &  ' /* conversion of deg. Centigrade to Kelvin [K] */')
112          CALL WRITE_0D_R8( gravity_mks, INDEX_NONE, 'gravity_mks=',
113         &  ' /* gravitational acceleration [m/s^2] */')
114          CALL WRITE_0D_R8( atmrho, INDEX_NONE, 'atmrho =',
115         & '  /* mean atmospheric density [kg/m^3] */')
116          CALL WRITE_0D_R8( atmcp, INDEX_NONE, 'atmcp =',
117         & '  /* mean atmospheric specific heat [J/kg/K] */')
118          CALL WRITE_0D_R8( flamb, INDEX_NONE, 'flamb =',
119         & '  /* latent heat of evaporation [J/kg] */')
120          CALL WRITE_0D_R8( flami, INDEX_NONE, 'flami =',
121         & '  /* latent heat of pure-ice melting [J/kg] */')
122          CALL WRITE_0D_R8( cvapor_fac, INDEX_NONE, 'cvapor_fac =',
123         &  ' /* const. for Saturation calculation [?] */')
124          CALL WRITE_0D_R8( cvapor_exp, INDEX_NONE, 'cvapor_exp =',
125         &  ' /* const. for Saturation calculation [?] */')
126          CALL WRITE_0D_R8( cvapor_fac_ice, INDEX_NONE, 'cvapor_fac_ice=',
127         &  ' /* const. for Saturation calculation [?] */')
128          CALL WRITE_0D_R8( cvapor_exp_ice, INDEX_NONE, 'cvapor_exp_ice=',
129         &  ' /* const. for Saturation calculation [?] */')
130          CALL WRITE_0D_R8( humid_fac, INDEX_NONE, 'humid_fac =',
131         &  ' /* humidity coef. in virtual temp. [(kg/kg)^-1] */')
132          CALL WRITE_0D_R8( gamma_blk, INDEX_NONE, 'gamma_blk =',
133         &  ' /* adiabatic lapse rate [?] */')
134          CALL WRITE_0D_R8( saltsat, INDEX_NONE, 'saltsat =',
135         &  ' /* reduction of Qsat over salty water [-] */')
136          CALL WRITE_0D_R8( cdrag_1, INDEX_NONE, 'cDrag_1 =',
137         &  ' /* coef used in drag calculation [?] */')
138          CALL WRITE_0D_R8( cdrag_2, INDEX_NONE, 'cDrag_2 =',
139         &  ' /* coef used in drag calculation [?] */')
140          CALL WRITE_0D_R8( cdrag_3, INDEX_NONE, 'cDrag_3 =',
141         &  ' /* coef used in drag calculation [?] */')
142          CALL WRITE_0D_R8( cstanton_1, INDEX_NONE, 'cStanton_1 =',
143         &  ' /* coef used in Stanton number calculation [?] */')
144          CALL WRITE_0D_R8( cstanton_2, INDEX_NONE, 'cStanton_2 =',
145         &  ' /* coef used in Stanton number calculation [?] */')
146          CALL WRITE_0D_R8( cdalton, INDEX_NONE, 'cDalton =',
147         &  ' /* coef used in Dalton number calculation [?] */')
148          CALL WRITE_0D_R8( exf_scal_BulkCdn, INDEX_NONE,
149         &  'exf_scal_BulkCdn=',
150         &  ' /* Drag coefficient scaling factor [-] */')
151          CALL WRITE_0D_R8( zolmin, INDEX_NONE, 'zolmin =',
152         &  ' /* minimum stability parameter [?] */')
153          CALL WRITE_0D_R8( psim_fac, INDEX_NONE, 'psim_fac =',
154         &  ' /* coef used in turbulent fluxes calculation [-] */')
155          CALL WRITE_0D_R8( zref, INDEX_NONE, 'zref =',
156         & '  /* reference height [ m ] */')
157          CALL WRITE_0D_R8( hu, INDEX_NONE, 'hu =',
158         & '  /* height of mean wind [ m ] */')
159          CALL WRITE_0D_R8( ht, INDEX_NONE, 'ht =',
160         & '  /* height of mean temperature [ m ] */')
161          CALL WRITE_0D_R8( hq, INDEX_NONE, 'hq =',
162         & '  /* height of mean spec.humidity [ m ] */')
163          CALL WRITE_0D_R8( umin, INDEX_NONE, 'uMin =',
164         &  ' /* minimum wind speed [m/s] */')
165          CALL WRITE_0D_L( useStabilityFct_overIce, INDEX_NONE,
166         &  'useStabilityFct_overIce=',
167         &  ' /* transfert Coeffs over sea-ice depend on stability */')
168          CALL WRITE_0D_R8( exf_iceCd, INDEX_NONE, 'exf_iceCd =',
169         &  ' /* drag coefficient over sea-ice (fixed) [-] */')
170          CALL WRITE_0D_R8( exf_iceCe, INDEX_NONE, 'exf_iceCe =',
171         &  ' /* transfert coeff. over sea-ice, for Evap (fixed) [-] */')
172          CALL WRITE_0D_R8( exf_iceCh, INDEX_NONE, 'exf_iceCh =',
173         &  ' /* transfert coeff. over sea-ice, Sens.Heat.(fixed)[-] */')
174          CALL WRITE_0D_R8( exf_albedo, INDEX_NONE, 'exf_albedo =',
175         & '  /* Sea-water albedo [-] */')
176          CALL WRITE_0D_R8( ocean_emissivity, INDEX_NONE,
177         &  'ocean_emissivity =',
178         &  ' /* longwave ocean-surface emissivity [-] */')
179          CALL WRITE_0D_R8( ice_emissivity, INDEX_NONE,'ice_emissivity =',
180         &  ' /* longwave seaice emissivity [-] */')
181          CALL WRITE_0D_R8(snow_emissivity, INDEX_NONE,'snow_emissivity =',
182         &  ' /* longwave snow  emissivity [-] */')
183          WRITE(msgBuf,'(A)') ' '
184          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
185         &                    SQUEEZE_RIGHT , myThid )
186    
187    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
188    C--   Print settings of some CPP flags.
189          WRITE(msgBuf,'(A)') ' EXF main CPP flags:'
190          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
191         &                    SQUEEZE_RIGHT , myThid )
192          WRITE(msgBuf,'(A)') ' '
193          CALL PRINT_MESSAGE( msgBuf, standardMessageUnit,
194         &                    SQUEEZE_RIGHT , myThid )
195    
196  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_ATM_TEMP
197        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 143  c--   Print settings of some CPP flags. Line 241  c--   Print settings of some CPP flags.
241       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
242  #endif  #endif
243    
244  c--   For each data set used the summary prints the calendar data  C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
245  c     and the corresponding file from which the data will be read.  
246    C--   For each data set used the summary prints the calendar data
247    C     and the corresponding file from which the data will be read.
248    
249  #ifndef ALLOW_ATM_WIND  #ifndef ALLOW_ATM_WIND
250  c--   Zonal wind stress.  C--   Zonal wind stress.
251        il = ilnblnk(ustressfile)        il = ilnblnk(ustressfile)
252        call cal_TimeInterval( ustressperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
253        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
254       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
255        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
256       &'   Zonal wind stress forcing starts at         ',       &'   Zonal wind stress forcing starts at         ',
257       &    (ustressstartdate(i), i=1,2), dayofweek(ustressstartdate(4)),       &    ustressstartdate
      &    '.'  
258        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
259       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
260        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
261       &'   Zonal wind stress forcing period is         ',       &'   Zonal wind stress forcing period is         ',
262       &    (timeint(i), i=1,2)       &    ustressperiod
263        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
264       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
265        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 174  c--   Zonal wind stress. Line 271  c--   Zonal wind stress.
271        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
272       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
273    
274  c--   Meridional wind stress.  C--   Meridional wind stress.
275        il = ilnblnk(vstressfile)        il = ilnblnk(vstressfile)
276        call cal_TimeInterval( vstressperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
277        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
278       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
279        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
280       &'   Meridional wind stress forcing starts at    ',       &'   Meridional wind stress forcing starts at    ',
281       &    (vstressstartdate(i), i=1,2), dayofweek(vstressstartdate(4)),       &    vstressstartdate
      &    '.'  
282        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
283       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
284        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
285       &'   Meridional wind stress forcing period is    ',       &'   Meridional wind stress forcing period is    ',
286       &    (timeint(i), i=1,2)       &    vstressperiod
287        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
288       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
289        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 203  c--   Meridional wind stress. Line 297  c--   Meridional wind stress.
297  #endif  #endif
298    
299  #ifndef ALLOW_ATM_TEMP  #ifndef ALLOW_ATM_TEMP
300  c--   Heat flux.  C--   Heat flux.
301        il = ilnblnk(hfluxfile)        il = ilnblnk(hfluxfile)
302        call cal_TimeInterval( hfluxperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
303        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
304       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
305        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
306       &'   Heat flux forcing starts at                ',       &'   Heat flux forcing starts at                ',
307       &    (hfluxstartdate(i), i=1,2), dayofweek(hfluxstartdate(4)),'.'       &    hfluxstartdate
308        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
309       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
310        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
311       &'   Heat flux forcing period is                 ',       &'   Heat flux forcing period is                 ',
312       &    (timeint(i), i=1,2)       &    hfluxperiod
313        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
314       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
315        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 229  c--   Heat flux. Line 321  c--   Heat flux.
321        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
322       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
323    
324  c--   Salt flux.  C--   Salt flux.
325        il = ilnblnk(sfluxfile)        il = ilnblnk(sfluxfile)
326        call cal_TimeInterval( sfluxperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
327        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
328       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
329        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
330       &'   Salt flux forcing starts at                 ',       &'   Salt flux forcing starts at                 ',
331       &    (sfluxstartdate(i), i=1,2), dayofweek(sfluxstartdate(4)),'.'       &    sfluxstartdate
332        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
333       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
334        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
335       &'   Salt flux forcing period is                 ',       &'   Salt flux forcing period is                 ',
336       &    (timeint(i), i=1,2)       &    sfluxperiod
337        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
338       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
339        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 257  c--   Salt flux. Line 347  c--   Salt flux.
347  #endif  #endif
348    
349  #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)  #if defined(ALLOW_ATM_TEMP) || defined(SHORTWAVE_HEATING)
350  c--   Net shortwave.  C--   Net shortwave.
351        il = ilnblnk(swfluxfile)        il = ilnblnk(swfluxfile)
352        call cal_TimeInterval( swfluxperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
353        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
354       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
355        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
356       &'   Net shortwave flux forcing starts at      ',       &'   Net shortwave flux forcing starts at      ',
357       &    (swfluxstartdate(i), i=1,2), dayofweek(swfluxstartdate(4)),       &    swfluxstartdate
      &    '.'  
358        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
359       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
360        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
361       &'   Net shortwave flux forcing period is      ',       &'   Net shortwave flux forcing period is      ',
362       &    (timeint(i), i=1,2)       &    swfluxperiod
363        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
364       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
365        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 286  c--   Net shortwave. Line 373  c--   Net shortwave.
373  #endif  #endif
374    
375  #ifdef ALLOW_ATM_WIND  #ifdef ALLOW_ATM_WIND
376  c--   Zonal wind.  C--   Zonal wind.
377        il = ilnblnk(uwindfile)        il = ilnblnk(uwindfile)
378        call cal_TimeInterval( uwindperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
379        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
380       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
381        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
382       &'   Zonal wind forcing starts at                ',       &'   Zonal wind forcing starts at                ',
383       &    (uwindstartdate(i), i=1,2), dayofweek(uwindstartdate(4)),       &    uwindstartdate
      &    '.'  
384        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
385       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
386        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
387       &'   Zonal wind forcing period is                ',       &'   Zonal wind forcing period is                ',
388       &    (timeint(i), i=1,2)       &    uwindperiod
389        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
390       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
391        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 313  c--   Zonal wind. Line 397  c--   Zonal wind.
397        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
398       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
399    
400  c--   Meridional wind.  C--   Meridional wind.
401        il = ilnblnk(vwindfile)        il = ilnblnk(vwindfile)
402        call cal_TimeInterval( vwindperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
403        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
404       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
405        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
406       &'   Meridional wind forcing starts at           ',       &'   Meridional wind forcing starts at           ',
407       &    (vwindstartdate(i), i=1,2), dayofweek(vwindstartdate(4)),       &    vwindstartdate
      &    '.'  
408        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
409       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
410        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
411       &'   Meridional wind forcing period is           ',       &'   Meridional wind forcing period is           ',
412       &    (timeint(i), i=1,2)       &    vwindperiod
413        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
414       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
415        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 342  c--   Meridional wind. Line 423  c--   Meridional wind.
423  #endif  #endif
424    
425  #ifdef ALLOW_ATM_TEMP  #ifdef ALLOW_ATM_TEMP
426  c--   Atmospheric temperature.  C--   Atmospheric temperature.
427        il = ilnblnk(atempfile)        il = ilnblnk(atempfile)
428        call cal_TimeInterval( atempperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
429        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
430       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
431        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
432       &'   Atmospheric temperature starts at           ',       &'   Atmospheric temperature starts at           ',
433       &    (atempstartdate(i), i=1,2), dayofweek(atempstartdate(4)),       &    atempstartdate
      &    '.'  
434        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
435       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
436        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
437       &'   Atmospheric temperature period is           ',       &'   Atmospheric temperature period is           ',
438       &    (timeint(i), i=1,2)       &    atempperiod
439        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
440       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
441        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 369  c--   Atmospheric temperature. Line 447  c--   Atmospheric temperature.
447        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
448       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
449    
450  c--   Atmospheric specific humidity.  C--   Atmospheric specific humidity.
451        il = ilnblnk(aqhfile)        il = ilnblnk(aqhfile)
452        call cal_TimeInterval( aqhperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
453        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
454       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
455        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
456       &'   Atmospheric specific humidity starts at     ',       &'   Atmospheric specific humidity starts at     ',
457       &    (aqhstartdate(i), i=1,2), dayofweek(aqhstartdate(4)),       &    aqhstartdate
      &    '.'  
458        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
459       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
460        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
461       &'   Atmospheric specific humidity period is     ',       &'   Atmospheric specific humidity period is     ',
462       &    (timeint(i), i=1,2)       &    aqhperiod
463        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
464       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
465        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 396  c--   Atmospheric specific humidity. Line 471  c--   Atmospheric specific humidity.
471        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
472       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
473    
474  c--   Net longwave.  C--   Net longwave.
475        il = ilnblnk(lwfluxfile)        il = ilnblnk(lwfluxfile)
476        call cal_TimeInterval( lwfluxperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
477        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
478       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
479        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
480       &'   Net longwave flux forcing starts at       ',       &'   Net longwave flux forcing starts at       ',
481       &    (lwfluxstartdate(i), i=1,2), dayofweek(lwfluxstartdate(4)),       &    lwfluxstartdate
      &    '.'  
482        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
483       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
484        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
485       &'   Net longwave flux forcing period is       ',       &'   Net longwave flux forcing period is       ',
486       &    (timeint(i), i=1,2)       &    lwfluxperiod
487        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
488       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
489        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 423  c--   Net longwave. Line 495  c--   Net longwave.
495        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
496       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
497    
498  c--   Precipitation.  C--   Precipitation.
499        il = ilnblnk(precipfile)        il = ilnblnk(precipfile)
500        call cal_TimeInterval( precipperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
501        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
502       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
503        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
504       &'   Precipitation data set starts at            ',       &'   Precipitation data set starts at            ',
505       &    (precipstartdate(i), i=1,2), dayofweek(precipstartdate(4)),       &    precipstartdate
      &'.'  
506        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
507       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
508        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
509       &'   Precipitation data period is                ',       &'   Precipitation data period is                ',
510       &    (timeint(i), i=1,2)       &    precipperiod
511        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
512       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
513        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 451  c--   Precipitation. Line 520  c--   Precipitation.
520       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
521  #endif  #endif
522    
523    C--   Evaporation.
524          write(msgbuf,'(a)') ' '
525          call print_message( msgbuf, standardmessageunit,
526         &                    SQUEEZE_RIGHT , mythid)
527  #ifdef EXF_READ_EVAP  #ifdef EXF_READ_EVAP
 c--   Evaporation.  
528        write(msgbuf,'(a)')        write(msgbuf,'(a)')
529       &'// EXF_READ_EVAP:                      defined'       &'// EXF_READ_EVAP:                      defined'
530        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
531       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
532        il = ilnblnk(evapfile)        il = ilnblnk(evapfile)
533        call cal_TimeInterval( evapperiod, 'secs', timeint, mythid )        write(msgbuf,'(a,f12.0)')
   
       write(msgbuf,'(a)')  
      &' '  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')  
534       &'   Evaporation starts at     ',       &'   Evaporation starts at     ',
535       &    (evapstartdate(i), i=1,2), dayofweek(evapstartdate(4)),       &    evapstartdate
      &    '.'  
536        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
537       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
538        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
539       &'   Evaporation period is     ',       &'   Evaporation period is     ',
540       &    (timeint(i), i=1,2)       &    evapperiod
541        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
542       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
543        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 490  c--   Evaporation. Line 555  c--   Evaporation.
555       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
556  #endif  #endif
557    
558    C--   Runoff.
559          write(msgbuf,'(a)') ' '
560          call print_message( msgbuf, standardmessageunit,
561         &                    SQUEEZE_RIGHT , mythid)
562  #ifdef ALLOW_RUNOFF  #ifdef ALLOW_RUNOFF
 c--   Runoff.  
563        write(msgbuf,'(a)')        write(msgbuf,'(a)')
564       &'// ALLOW_RUNOFF:                       defined'       &'// ALLOW_RUNOFF:                       defined'
565        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
566       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
567        il = ilnblnk(runofffile)        il = ilnblnk(runofffile)
568        call cal_TimeInterval( runoffperiod, 'secs', timeint, mythid )        write(msgbuf,'(a,f12.0)')
569         &'   Runoff starts at     ',
570        write(msgbuf,'(a)')       &    runoffstartdate
      &' '  
       call print_message( msgbuf, standardmessageunit,  
      &                    SQUEEZE_RIGHT , mythid)  
       write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')  
      &'   Runnoff starts at     ',  
      &    (runoffstartdate(i), i=1,2), dayofweek(runoffstartdate(4)),  
      &    '.'  
571        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
572       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
573        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
574       &'   Runoff period is     ',       &'   Runoff period is     ',
575       &    (timeint(i), i=1,2)       &    runoffperiod
576        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
577       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
578        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 530  c--   Runoff. Line 591  c--   Runoff.
591  #endif /* ALLOW_RUNOFF */  #endif /* ALLOW_RUNOFF */
592    
593  #ifdef DOWNWARD_RADIATION  #ifdef DOWNWARD_RADIATION
594  c--   Downward shortwave.  C--   Downward shortwave.
595        il = ilnblnk(swdownfile)        il = ilnblnk(swdownfile)
596        call cal_TimeInterval( swdownperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
597        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
598       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
599        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
600       &'   Downward shortwave flux forcing starts at      ',       &'   Downward shortwave flux forcing starts at      ',
601       &    (swdownstartdate(i), i=1,2), dayofweek(swdownstartdate(4)),       &    swdownstartdate
      &    '.'  
602        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
603       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
604        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
605       &'   Downward shortwave flux forcing period is      ',       &'   Downward shortwave flux forcing period is      ',
606       &    (timeint(i), i=1,2)       &    swdownperiod
607        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
608       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
609        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 557  c--   Downward shortwave. Line 615  c--   Downward shortwave.
615        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
616       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
617    
618  c--   Downward longwave.  C--   Downward longwave.
619        il = ilnblnk(lwdownfile)        il = ilnblnk(lwdownfile)
620        call cal_TimeInterval( lwdownperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
621        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
622       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
623        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
624       &'   Downward longwave flux forcing starts at       ',       &'   Downward longwave flux forcing starts at       ',
625       &    (lwdownstartdate(i), i=1,2), dayofweek(lwdownstartdate(4)),       &    lwdownstartdate
      &    '.'  
626        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
627       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
628        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
629       &'   Downward longwave flux forcing period is       ',       &'   Downward longwave flux forcing period is       ',
630       &    (timeint(i), i=1,2)       &    lwdownperiod
631        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
632       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
633        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 586  c--   Downward longwave. Line 641  c--   Downward longwave.
641  #endif  #endif
642    
643  #ifdef ATMOSPHERIC_LOADING  #ifdef ATMOSPHERIC_LOADING
644  c--   Atmospheric pressure.  C--   Atmospheric pressure.
645        il = ilnblnk(apressurefile)        il = ilnblnk(apressurefile)
646        call cal_TimeInterval( apressureperiod, 'secs', timeint, mythid )        write(msgbuf,'(a)') ' '
       write(msgbuf,'(a)')  
      &' '  
647        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
648       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
649        write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')        write(msgbuf,'(a,f12.0)')
650       &'   Atmospheric pressure forcing starts at      ',       &'   Atmospheric pressure forcing starts at      ',
651       &    (apressurestartdate(i), i=1,2),       &    apressurestartdate
      &    dayofweek(apressurestartdate(4)), '.'  
652        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
653       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
654        write(msgbuf,'(a,i9.8,i7.6)')        write(msgbuf,'(a,f12.0)')
655       &'   Atmospheric pressure forcing period is      ',       &'   Atmospheric pressure forcing period is      ',
656       &    (timeint(i), i=1,2)       &    apressureperiod
657        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
658       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
659        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 614  c--   Atmospheric pressure. Line 666  c--   Atmospheric pressure.
666       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
667  #endif  #endif
668    
669        write(msgbuf,'(a)')        write(msgbuf,'(a)') ' '
      &' '  
670        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
671       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
672        write(msgbuf,'(a)')        write(msgbuf,'(a)')
# Line 630  c--   Atmospheric pressure. Line 681  c--   Atmospheric pressure.
681       &'// ======================================================='       &'// ======================================================='
682        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
683       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
684          write(msgbuf,'(a)') ' '
685          call print_message( msgbuf, standardmessageunit,
686         &                    SQUEEZE_RIGHT , mythid)
687    
688    C---+----1----+----2----+----3----+----4----+----5----+----6----+----7-|--+----|
689    
690          call print_message( msgbuf, standardmessageunit,
691         &                    SQUEEZE_RIGHT , mythid)
692          write(msgbuf,'(a)')
693         &'// ======================================================='
694          call print_message( msgbuf, standardmessageunit,
695         &                    SQUEEZE_RIGHT , mythid)
696          write(msgbuf,'(a)')
697         &'// External forcing climatology configuration >>> START <<<'
698          call print_message( msgbuf, standardmessageunit,
699         &                    SQUEEZE_RIGHT , mythid)
700          write(msgbuf,'(a)')
701         &'// ======================================================='
702          call print_message( msgbuf, standardmessageunit,
703         &                    SQUEEZE_RIGHT , mythid)
704          write(msgbuf,'(a)') ' '
705          call print_message( msgbuf, standardmessageunit,
706         &                    SQUEEZE_RIGHT , mythid)
707    
708    C     For each data set used the summary prints the calendar data
709    C     and the corresponding file from which the data will be read.
710    
711    #ifdef ALLOW_CLIMSST_RELAXATION
712          write(msgbuf,'(a)')
713         &'// ALLOW_CLIMSST_RELAXATION:           defined'
714          call print_message( msgbuf, standardmessageunit,
715         &                    SQUEEZE_RIGHT , mythid)
716    #else
717          write(msgbuf,'(a)')
718         &'// ALLOW_CLIMSST_RELAXATION:       NOT defined'
719          call print_message( msgbuf, standardmessageunit,
720         &                    SQUEEZE_RIGHT , mythid)
721    #endif
722    
723    #ifdef ALLOW_CLIMSSS_RELAXATION
724          write(msgbuf,'(a)')
725         &'// ALLOW_CLIMSSS_RELAXATION:           defined'
726          call print_message( msgbuf, standardmessageunit,
727         &                    SQUEEZE_RIGHT , mythid)
728    #else
729          write(msgbuf,'(a)')
730         &'// ALLOW_CLIMSSS_RELAXATION:       NOT defined'
731          call print_message( msgbuf, standardmessageunit,
732         &                    SQUEEZE_RIGHT , mythid)
733    #endif
734    
735    C     The climatological data sets are assumed to contain monthly
736    C     data. This can be changed in a later version to an arbitrary
737    C     number of intervals during a given year.
738    
739    #ifdef ALLOW_CLIMSST_RELAXATION
740    C     Relaxation to SST climatology.
741          il = ilnblnk(climsstfile)
742        write(msgbuf,'(a)')        write(msgbuf,'(a)')
743       &' '       &' '
744        call print_message( msgbuf, standardmessageunit,        call print_message( msgbuf, standardmessageunit,
745       &                    SQUEEZE_RIGHT , mythid)       &                    SQUEEZE_RIGHT , mythid)
746          write(msgbuf,'(a,f12.0)')
747         &'   Climatological SST starts at         ',
748         &    climsststartdate
749          call print_message( msgbuf, standardmessageunit,
750         &                    SQUEEZE_RIGHT , mythid)
751          write(msgbuf,'(a,f12.0)')
752         &'   Climatological SST period is         ',
753         &    climsstperiod
754          call print_message( msgbuf, standardmessageunit,
755         &                    SQUEEZE_RIGHT , mythid)
756          write(msgbuf,'(a)')
757         &'   Climatological SST is read from file:'
758          call print_message( msgbuf, standardmessageunit,
759         &                    SQUEEZE_RIGHT , mythid)
760          write(msgbuf,'(a,a,a)')
761         &'   >>  ',climsstfile(1:il),'  <<'
762          call print_message( msgbuf, standardmessageunit,
763         &                    SQUEEZE_RIGHT , mythid)
764    #endif
765    
766    #ifdef ALLOW_CLIMSSS_RELAXATION
767    C     Relaxation to SSS climatology.
768          il = ilnblnk(climsssfile)
769          write(msgbuf,'(a)')
770         &' '
771          call print_message( msgbuf, standardmessageunit,
772         &                    SQUEEZE_RIGHT , mythid)
773          write(msgbuf,'(a,f12.0)')
774         &'   Climatological SSS starts at         ',
775         &    climsssstartdate
776          call print_message( msgbuf, standardmessageunit,
777         &                    SQUEEZE_RIGHT , mythid)
778          write(msgbuf,'(a,f12.0)')
779         &'   Climatological SSS period is         ',
780         &    climsssperiod
781          call print_message( msgbuf, standardmessageunit,
782         &                    SQUEEZE_RIGHT , mythid)
783          write(msgbuf,'(a)')
784         &'   Climatological SSS is read from file:'
785          call print_message( msgbuf, standardmessageunit,
786         &                    SQUEEZE_RIGHT , mythid)
787          write(msgbuf,'(a,a,a)')
788         &'   >>  ',climsssfile(1:il),'  <<'
789          call print_message( msgbuf, standardmessageunit,
790         &                    SQUEEZE_RIGHT , mythid)
791    #endif
792    
793          write(msgbuf,'(a)') ' '
794          call print_message( msgbuf, standardmessageunit,
795         &                    SQUEEZE_RIGHT , mythid)
796          write(msgbuf,'(a)')
797         &'// ======================================================='
798          call print_message( msgbuf, standardmessageunit,
799         &                    SQUEEZE_RIGHT , mythid)
800          write(msgbuf,'(a)')
801         &'// External forcing climatology configuration  >>> END <<<'
802          call print_message( msgbuf, standardmessageunit,
803         &                    SQUEEZE_RIGHT , mythid)
804          write(msgbuf,'(a)')
805         &'// ======================================================='
806          call print_message( msgbuf, standardmessageunit,
807         &                    SQUEEZE_RIGHT , mythid)
808          write(msgbuf,'(a)') ' '
809          call print_message( msgbuf, standardmessageunit,
810         &                    SQUEEZE_RIGHT , mythid)
811    
812          _END_MASTER( myThid )
813    
814        end        RETURN
815          END

Legend:
Removed from v.1.6  
changed lines
  Added in v.1.16

  ViewVC Help
Powered by ViewVC 1.1.22