/[MITgcm]/MITgcm/pkg/ctrl/ctrl_summary.F
ViewVC logotype

Annotation of /MITgcm/pkg/ctrl/ctrl_summary.F

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


Revision 1.2 - (hide annotations) (download)
Tue Jun 24 16:07:07 2003 UTC (20 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint51k_post, checkpoint51o_pre, checkpoint51l_post, checkpoint51, checkpoint51f_post, checkpoint51d_post, checkpoint51t_post, checkpoint51n_post, checkpoint51s_post, checkpoint51j_post, checkpoint51n_pre, checkpoint51l_pre, checkpoint51q_post, checkpoint51b_pre, checkpoint51h_pre, branchpoint-genmake2, checkpoint51r_post, checkpoint51i_post, checkpoint51b_post, checkpoint51c_post, checkpoint51i_pre, checkpoint51e_post, checkpoint51o_post, checkpoint51f_pre, checkpoint51g_post, checkpoint51m_post, checkpoint51a_post, checkpoint51p_post
Branch point for: branch-genmake2, branch-nonh, tg2-branch, checkpoint51n_branch
Changes since 1.1: +342 -0 lines
Merging for c51 vs. e34

1 heimbach 1.2 C $Header: /u/gcmpack/MITgcm/pkg/ctrl/Attic/ctrl_summary.F,v 1.1.2.1 2002/02/05 20:23:58 heimbach Exp $
2    
3     #include "CTRL_CPPOPTIONS.h"
4    
5    
6     subroutine ctrl_Summary(
7     I mythid
8     & )
9    
10     c ==================================================================
11     c SUBROUTINE ctrl_Summary
12     c ==================================================================
13     c
14     c o Summarize the control vector part of the ECCO release.
15     c
16     c started: Christian Eckert eckert@mit.edu 06-Mar-2000
17     c
18     c changed: Christian Eckert eckert@mit.edu
19     c
20     c ==================================================================
21     c SUBROUTINE ctrl_Summary
22     c ==================================================================
23    
24     implicit none
25    
26     c == global variables ==
27    
28     #include "EEPARAMS.h"
29     #include "SIZE.h"
30    
31     #ifdef ALLOW_CALENDAR
32     # include "cal.h"
33     #endif
34     #include "ctrl.h"
35    
36     c == routine arguments ==
37    
38     integer mythid
39    
40     c == local variables ==
41    
42     integer bi,bj
43     integer i,k
44     integer il
45     integer timeint(4)
46     integer nwetcenter
47     integer nwetsouth
48     integer nwetwest
49    
50     character*(max_len_mbuf) msgbuf
51    
52     c == external ==
53    
54     integer ilnblnk
55     external ilnblnk
56    
57     c == end of interface ==
58    
59     write(msgbuf,'(a)')
60     &' '
61     call print_message( msgbuf, standardmessageunit,
62     & SQUEEZE_RIGHT , mythid)
63     write(msgbuf,'(a)')
64     &'// ======================================================='
65     call print_message( msgbuf, standardmessageunit,
66     & SQUEEZE_RIGHT , mythid)
67     write(msgbuf,'(a)')
68     &'// ECCO control vector configuration >>> START <<<'
69     call print_message( msgbuf, standardmessageunit,
70     & SQUEEZE_RIGHT , mythid)
71     write(msgbuf,'(a)')
72     &'// ======================================================='
73     call print_message( msgbuf, standardmessageunit,
74     & SQUEEZE_RIGHT , mythid)
75     write(msgbuf,'(a)')
76     &' '
77     call print_message( msgbuf, standardmessageunit,
78     & SQUEEZE_RIGHT , mythid)
79    
80     write(msgbuf,'(a)')
81     &' Total number of ocean points per tile:'
82     call print_message( msgbuf, standardmessageunit,
83     & SQUEEZE_RIGHT , mythid)
84     write(msgbuf,'(a)')
85     &' --------------------------------------'
86     call print_message( msgbuf, standardmessageunit,
87     & SQUEEZE_RIGHT , mythid)
88     write(msgbuf,'(a)')
89     &' '
90     call print_message( msgbuf, standardmessageunit,
91     & SQUEEZE_RIGHT , mythid)
92     write(msgbuf,'(a,i8)') ' snx*sny*nr = ',snx*sny*nr
93     call print_message( msgbuf, standardmessageunit,
94     & SQUEEZE_RIGHT , mythid)
95     write(msgbuf,'(a)')
96     &' '
97     call print_message( msgbuf, standardmessageunit,
98     & SQUEEZE_RIGHT , mythid)
99     write(msgbuf,'(a)')
100     &' Number of ocean points per tile:'
101     call print_message( msgbuf, standardmessageunit,
102     & SQUEEZE_RIGHT , mythid)
103     write(msgbuf,'(a)')
104     &' --------------------------------'
105     call print_message( msgbuf, standardmessageunit,
106     & SQUEEZE_RIGHT , mythid)
107     do bj = 1,nsy
108     do bi = 1,nsx
109     nwetcenter = 0
110     nwetsouth = 0
111     nwetwest = 0
112     do k = 1,nr
113     nwetcenter = nwetcenter + nwetctile(bi,bj,k)
114     nwetsouth = nwetsouth + nwetstile(bi,bj,k)
115     nwetwest = nwetwest + nwetwtile(bi,bj,k)
116     enddo
117     write(msgbuf,'(a,i5.4,i5.4,i7.6,i7.6,i7.6)')
118     & ' bi,bj,#(c/s/w):',bi,bj,nwetcenter,
119     & nwetsouth,
120     & nwetwest
121     call print_message( msgbuf, standardmessageunit,
122     & SQUEEZE_RIGHT , mythid)
123     enddo
124     enddo
125    
126     #ifdef ALLOW_THETA0_CONTROL
127     write(msgbuf,'(a)')
128     &' '
129     call print_message( msgbuf, standardmessageunit,
130     & SQUEEZE_RIGHT , mythid)
131     write(msgbuf,'(a)')
132     &' Initial state temperature contribution:'
133     call print_message( msgbuf, standardmessageunit,
134     & SQUEEZE_RIGHT , mythid)
135     write(msgbuf,'(a,i5.4)')
136     &' Control variable index: ',ncvarindex(1)
137     call print_message( msgbuf, standardmessageunit,
138     & SQUEEZE_RIGHT , mythid)
139     #endif
140     #ifdef ALLOW_SALT0_CONTROL
141     write(msgbuf,'(a)')
142     &' '
143     call print_message( msgbuf, standardmessageunit,
144     & SQUEEZE_RIGHT , mythid)
145     write(msgbuf,'(a)')
146     &' Initial state salinity contribution:'
147     call print_message( msgbuf, standardmessageunit,
148     & SQUEEZE_RIGHT , mythid)
149     write(msgbuf,'(a,i5.4)')
150     &' Control variable index: ',ncvarindex(2)
151     call print_message( msgbuf, standardmessageunit,
152     & SQUEEZE_RIGHT , mythid)
153     #endif
154     #ifdef ALLOW_HFLUX_CONTROL
155     write(msgbuf,'(a)')
156     &' '
157     call print_message( msgbuf, standardmessageunit,
158     & SQUEEZE_RIGHT , mythid)
159     write(msgbuf,'(a)')
160     &' Heat flux contribution:'
161     call print_message( msgbuf, standardmessageunit,
162     & SQUEEZE_RIGHT , mythid)
163     write(msgbuf,'(a,i5.4)')
164     &' Control variable index: ',ncvarindex(3)
165     call print_message( msgbuf, standardmessageunit,
166     & SQUEEZE_RIGHT , mythid)
167    
168     il = ilnblnk(xx_hflux_file)
169     call cal_TimeInterval( xx_hfluxperiod, 'secs', timeint, mythid )
170    
171     write(msgbuf,'(a)')
172     &' '
173     call print_message( msgbuf, standardmessageunit,
174     & SQUEEZE_RIGHT , mythid)
175     write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')
176     &' Heat flux contribution starts at: ',
177     & (xx_hfluxstartdate(i), i=1,2),
178     & dayofweek(xx_hfluxstartdate(4)),'.'
179     call print_message( msgbuf, standardmessageunit,
180     & SQUEEZE_RIGHT , mythid)
181     write(msgbuf,'(a,i9.8,i7.6)')
182     &' Heat flux contribution period is: ',
183     & (timeint(i), i=1,2)
184     call print_message( msgbuf, standardmessageunit,
185     & SQUEEZE_RIGHT , mythid)
186     write(msgbuf,'(a)')
187     &' Heat flux contribution is read from file: '
188     call print_message( msgbuf, standardmessageunit,
189     & SQUEEZE_RIGHT , mythid)
190     write(msgbuf,'(a,a,a)')
191     &' >> ',xx_hflux_file(1:il),' <<'
192     call print_message( msgbuf, standardmessageunit,
193     & SQUEEZE_RIGHT , mythid)
194     #endif
195     #ifdef ALLOW_SFLUX_CONTROL
196     write(msgbuf,'(a)')
197     &' '
198     call print_message( msgbuf, standardmessageunit,
199     & SQUEEZE_RIGHT , mythid)
200     write(msgbuf,'(a)')
201     &' Salt flux contribution:'
202     call print_message( msgbuf, standardmessageunit,
203     & SQUEEZE_RIGHT , mythid)
204     write(msgbuf,'(a,i5.4)')
205     &' Control varibale index: ',ncvarindex(4)
206     call print_message( msgbuf, standardmessageunit,
207     & SQUEEZE_RIGHT , mythid)
208    
209     il = ilnblnk(xx_sflux_file)
210     call cal_TimeInterval( xx_sfluxperiod, 'secs', timeint, mythid )
211    
212     write(msgbuf,'(a)')
213     &' '
214     call print_message( msgbuf, standardmessageunit,
215     & SQUEEZE_RIGHT , mythid)
216     write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')
217     &' Salt flux contribution starts at: ',
218     & (xx_sfluxstartdate(i), i=1,2),
219     & dayofweek(xx_sfluxstartdate(4)),'.'
220     call print_message( msgbuf, standardmessageunit,
221     & SQUEEZE_RIGHT , mythid)
222     write(msgbuf,'(a,i9.8,i7.6)')
223     &' Salt flux contribution period is: ',
224     & (timeint(i), i=1,2)
225     call print_message( msgbuf, standardmessageunit,
226     & SQUEEZE_RIGHT , mythid)
227     write(msgbuf,'(a)')
228     &' Salt flux contribution is read from file: '
229     call print_message( msgbuf, standardmessageunit,
230     & SQUEEZE_RIGHT , mythid)
231     write(msgbuf,'(a,a,a)')
232     &' >> ',xx_sflux_file(1:il),' <<'
233     call print_message( msgbuf, standardmessageunit,
234     & SQUEEZE_RIGHT , mythid)
235     #endif
236     #ifdef ALLOW_USTRESS_CONTROL
237     write(msgbuf,'(a)')
238     &' '
239     call print_message( msgbuf, standardmessageunit,
240     & SQUEEZE_RIGHT , mythid)
241     write(msgbuf,'(a)')
242     &' Zonal wind stress contribution:'
243     call print_message( msgbuf, standardmessageunit,
244     & SQUEEZE_RIGHT , mythid)
245     write(msgbuf,'(a,i5.4)')
246     &' Control variable index: ',ncvarindex(5)
247     call print_message( msgbuf, standardmessageunit,
248     & SQUEEZE_RIGHT , mythid)
249    
250     il = ilnblnk(xx_tauu_file)
251     call cal_TimeInterval( xx_tauuperiod, 'secs', timeint, mythid )
252    
253     write(msgbuf,'(a)')
254     &' '
255     call print_message( msgbuf, standardmessageunit,
256     & SQUEEZE_RIGHT , mythid)
257     write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')
258     &' Zonal wind stress contribution starts at: ',
259     & (xx_tauustartdate(i), i=1,2),
260     & dayofweek(xx_tauustartdate(4)),'.'
261     call print_message( msgbuf, standardmessageunit,
262     & SQUEEZE_RIGHT , mythid)
263     write(msgbuf,'(a,i9.8,i7.6)')
264     &' Zonal wind stress contribution period is: ',
265     & (timeint(i), i=1,2)
266     call print_message( msgbuf, standardmessageunit,
267     & SQUEEZE_RIGHT , mythid)
268     write(msgbuf,'(a)')
269     &' Zonal wind stress contribution is read from file: '
270     call print_message( msgbuf, standardmessageunit,
271     & SQUEEZE_RIGHT , mythid)
272     write(msgbuf,'(a,a,a)')
273     &' >> ',xx_tauu_file(1:il),' <<'
274     call print_message( msgbuf, standardmessageunit,
275     & SQUEEZE_RIGHT , mythid)
276     #endif
277     #ifdef ALLOW_VSTRESS_CONTROL
278     write(msgbuf,'(a)')
279     &' '
280     call print_message( msgbuf, standardmessageunit,
281     & SQUEEZE_RIGHT , mythid)
282     write(msgbuf,'(a)')
283     &' Meridional wind stress contribution:'
284     call print_message( msgbuf, standardmessageunit,
285     & SQUEEZE_RIGHT , mythid)
286     write(msgbuf,'(a,i5.4)')
287     &' Control variable index: ',ncvarindex(6)
288     call print_message( msgbuf, standardmessageunit,
289     & SQUEEZE_RIGHT , mythid)
290    
291     il = ilnblnk(xx_tauv_file)
292     call cal_TimeInterval( xx_tauvperiod, 'secs', timeint, mythid )
293    
294     write(msgbuf,'(a)')
295     &' '
296     call print_message( msgbuf, standardmessageunit,
297     & SQUEEZE_RIGHT , mythid)
298     write(msgbuf,'(a,i9.8,i7.6,1x,a,a)')
299     &' Merid. wind stress contribution starts at: ',
300     & (xx_hfluxstartdate(i), i=1,2),
301     & dayofweek(xx_hfluxstartdate(4)),'.'
302     call print_message( msgbuf, standardmessageunit,
303     & SQUEEZE_RIGHT , mythid)
304     write(msgbuf,'(a,i9.8,i7.6)')
305     &' Merid. wind stress contribution period is: ',
306     & (timeint(i), i=1,2)
307     call print_message( msgbuf, standardmessageunit,
308     & SQUEEZE_RIGHT , mythid)
309     write(msgbuf,'(a)')
310     &' Merid. wind stress contribution is read from file: '
311     call print_message( msgbuf, standardmessageunit,
312     & SQUEEZE_RIGHT , mythid)
313     write(msgbuf,'(a,a,a)')
314     &' >> ',xx_tauv_file(1:il),' <<'
315     call print_message( msgbuf, standardmessageunit,
316     & SQUEEZE_RIGHT , mythid)
317     #endif
318    
319     write(msgbuf,'(a)')
320     &' '
321     call print_message( msgbuf, standardmessageunit,
322     & SQUEEZE_RIGHT , mythid)
323     write(msgbuf,'(a)')
324     &'// ======================================================='
325     call print_message( msgbuf, standardmessageunit,
326     & SQUEEZE_RIGHT , mythid)
327     write(msgbuf,'(a)')
328     &'// ECCO control vector configuration >>> END <<<'
329     call print_message( msgbuf, standardmessageunit,
330     & SQUEEZE_RIGHT , mythid)
331     write(msgbuf,'(a)')
332     &'// ======================================================='
333     call print_message( msgbuf, standardmessageunit,
334     & SQUEEZE_RIGHT , mythid)
335     write(msgbuf,'(a)')
336     &' '
337     call print_message( msgbuf, standardmessageunit,
338     & SQUEEZE_RIGHT , mythid)
339    
340     return
341     end
342    

  ViewVC Help
Powered by ViewVC 1.1.22