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

Legend:
Removed from v.1.1  
changed lines
  Added in v.1.19

  ViewVC Help
Powered by ViewVC 1.1.22