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

Legend:
Removed from v.1.2  
changed lines
  Added in v.1.14

  ViewVC Help
Powered by ViewVC 1.1.22