/[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.4 - (hide annotations) (download)
Tue Oct 9 00:00:01 2007 UTC (16 years, 8 months ago) by jmc
Branch: MAIN
CVS Tags: checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62c, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62w, checkpoint62x, checkpoint60, checkpoint61, checkpoint62, checkpoint59q, checkpoint59p, checkpoint59r, checkpoint59m, checkpoint59l, checkpoint59o, checkpoint59n, checkpoint59i, checkpoint59k, checkpoint62b, checkpoint61f, checkpoint61n, checkpoint59j, checkpoint61q, checkpoint61e, checkpoint61g, checkpoint61d, checkpoint61b, checkpoint61c, checkpoint61a, checkpoint61o, checkpoint61l, checkpoint61m, checkpoint61j, checkpoint61k, checkpoint61h, checkpoint61i, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61p, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.3: +3 -2 lines
add missing cvs $Header:$ or $Name:$

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

  ViewVC Help
Powered by ViewVC 1.1.22