/[MITgcm]/MITgcm/pkg/ecco/cost_driftw.F
ViewVC logotype

Annotation of /MITgcm/pkg/ecco/cost_driftw.F

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


Revision 1.3 - (hide annotations) (download)
Mon Mar 28 23:49:49 2005 UTC (19 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint57f_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint57i_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint57m_post, checkpoint58n_post, checkpoint57g_pre, checkpoint58h_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint58q_post, checkpoint58j_post, checkpoint57r_post, checkpoint58, checkpoint57h_done, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58o_post, checkpoint57z_post, checkpoint58k_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.2: +7 -5 lines
Adding counters to cost terms.

1 heimbach 1.3 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_driftw.F,v 1.2 2004/10/11 16:38:53 heimbach Exp $
2 heimbach 1.1
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_driftw(
7     I myiter,
8     I mytime,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE cost_Driftw
14     c ==================================================================
15     c
16     c o Evaluate cost function contribution of the w difference
17     c between the first and the last year.
18     c
19     c started: from cost_drift
20     c
21     c Armin Koehl akoehl@ucsd.edu 26-Feb-2002
22     c
23     c ==================================================================
24     c SUBROUTINE cost_Driftw
25     c ==================================================================
26    
27     implicit none
28    
29     c == global variables ==
30    
31     #include "EEPARAMS.h"
32     #include "SIZE.h"
33     #include "GRID.h"
34     #include "DYNVARS.h"
35    
36     #include "cal.h"
37     #include "ecco_cost.h"
38     #include "ctrl.h"
39     #include "ctrl_dummy.h"
40     #include "optim.h"
41    
42     c == routine arguments ==
43    
44     integer myiter
45     _RL mytime
46     integer mythid
47    
48     c == local variables ==
49    
50     _RS one_rs
51     parameter( one_rs = 1. )
52    
53     integer bi,bj
54     integer i,j,k
55     integer itlo,ithi
56     integer jtlo,jthi
57     integer jmin,jmax
58     integer imin,imax
59     integer irec
60     integer ilw
61     integer nf, nl
62    
63     _RL fctilew
64     _RL fcthread_wdrift
65    
66     character*(80) fnamew
67    
68     logical doglobalread
69     logical ladinit
70    
71     character*(MAX_LEN_MBUF) msgbuf
72    
73     c == external functions ==
74    
75     integer ilnblnk
76     external ilnblnk
77    
78     c == end of interface ==
79    
80     jtlo = mybylo(mythid)
81     jthi = mybyhi(mythid)
82     itlo = mybxlo(mythid)
83     ithi = mybxhi(mythid)
84     jmin = 1
85     jmax = sny
86     imin = 1
87     imax = snx
88    
89     c-- Read tiled data.
90     doglobalread = .false.
91     ladinit = .false.
92    
93     #ifdef ALLOW_DRIFTW_COST_CONTRIBUTION
94    
95     if (optimcycle .ge. 0) then
96     ilw = ilnblnk( wbarfile )
97     write(fnamew(1:80),'(2a,i10.10)')
98     & wbarfile(1:ilw),'.',optimcycle
99     endif
100    
101     if (nmonsrec.lt.12) then
102     print*
103     print*,' cost_Driftw: assimilation period smaller'
104     print*,' than 1 year, no drift computed.'
105     print*
106     stop ' ... stopped in cost_Driftw.'
107     endif
108    
109     fcthread_wdrift = 0. _d 0
110    
111     do bj = jtlo,jthi
112     do bi = itlo,ithi
113     do k = 1,nr
114     do j = jmin,jmax
115     do i = imin,imax
116     wfmean(i,j,k,bi,bj) = 0.0
117     wlmean(i,j,k,bi,bj) = 0.0
118     enddo
119     enddo
120     enddo
121     enddo
122     enddo
123    
124     nf = 0
125     nl = 0
126    
127     c-- Loop over records.
128     do irec = 1,12
129    
130     c-- Read time averages and the monthly mean data.
131     call active_read_xyz( fnamew, wbar, irec,
132     & doglobalread, ladinit,
133     & optimcycle, mythid,
134     & xx_wbar_mean_dummy )
135    
136     nf = nf + 1
137     do bj = jtlo,jthi
138     do bi = itlo,ithi
139     do k = 1,nr
140     do j = jmin,jmax
141     do i = imin,imax
142     wfmean(i,j,k,bi,bj) = wfmean(i,j,k,bi,bj) +
143     & wbar(i,j,k,bi,bj)
144     enddo
145     enddo
146     enddo
147     enddo
148     enddo
149    
150     enddo
151    
152     do irec = nmonsrec-12+1, nmonsrec
153    
154     c-- Read time averages and the monthly mean data.
155     call active_read_xyz( fnamew, wbar, irec,
156     & doglobalread, ladinit,
157     & optimcycle, mythid,
158     & xx_wbar_mean_dummy )
159    
160     nl = nl + 1
161    
162     do bj = jtlo,jthi
163     do bi = itlo,ithi
164     do k = 1,nr
165     do j = jmin,jmax
166     do i = imin,imax
167     wlmean(i,j,k,bi,bj) = wlmean(i,j,k,bi,bj) +
168     & wbar(i,j,k,bi,bj)
169     enddo
170     enddo
171     enddo
172     enddo
173     enddo
174    
175     enddo
176    
177    
178     do bj = jtlo,jthi
179     do bi = itlo,ithi
180    
181     c-- Loop over the model layers
182     fctilew = 0. _d 0
183    
184     do k = 1,nr
185    
186     c-- Compute model misfit and cost function term for
187     c the vertical velovity field. The error is 1e-4 m/s.
188     do j = jmin,jmax
189 heimbach 1.3 do i = imin,imax
190     if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
191 heimbach 1.1 fctilew = fctilew +
192     & (2.5e11*cosphi(i,j,bi,bj)*
193     & (wlmean(i,j,k,bi,bj)/nl - wfmean(i,j,k,bi,bj)/nf)*
194     & (wlmean(i,j,k,bi,bj)/nl - wfmean(i,j,k,bi,bj)/nf))
195 heimbach 1.3 if ( cosphi(i,j,bi,bj) .ne. 0. )
196     & num_wdrift(bi,bj) = num_wdrift(bi,bj) + 1. _d 0
197     endif
198     enddo
199 heimbach 1.1 enddo
200    
201     enddo
202     c-- End of loop over layers.
203    
204     fcthread_wdrift = fcthread_wdrift + fctilew
205     objf_wdrift(bi,bj) = objf_wdrift(bi,bj) + fctilew
206    
207     #ifdef ECCO_VERBOSE
208     c-- Print cost function for each tile in each thread.
209     write(msgbuf,'(a)') ' '
210     call print_message( msgbuf, standardmessageunit,
211     & SQUEEZE_RIGHT , mythid)
212     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
213     & ' cost_Driftw: irec,bi,bj = ',irec,bi,bj
214     call print_message( msgbuf, standardmessageunit,
215     & SQUEEZE_RIGHT , mythid)
216     write(msgbuf,'(a,d22.15)')
217     & ' cost function (wvel) = ',
218     & fctilet+fctiles
219     call print_message( msgbuf, standardmessageunit,
220     & SQUEEZE_RIGHT , mythid)
221     write(msgbuf,'(a)') ' '
222     call print_message( msgbuf, standardmessageunit,
223     & SQUEEZE_RIGHT , mythid)
224     #endif
225    
226     enddo
227     enddo
228    
229     #ifdef ECCO_VERBOSE
230     c-- Print cost function for all tiles.
231     _GLOBAL_SUM_R8( fcthread_tdrift , myThid )
232     _GLOBAL_SUM_R8( fcthread_tdrifs , myThid )
233     write(msgbuf,'(a)') ' '
234     call print_message( msgbuf, standardmessageunit,
235     & SQUEEZE_RIGHT , mythid)
236     write(msgbuf,'(a,i8.8)')
237     & ' cost_Drift: irec = ',irec
238     call print_message( msgbuf, standardmessageunit,
239     & SQUEEZE_RIGHT , mythid)
240     write(msgbuf,'(a,a,d22.15)')
241     & ' cost function value',
242     & ' (wvel) = ',fcthread_tdrifw
243     call print_message( msgbuf, standardmessageunit,
244     & SQUEEZE_RIGHT , mythid)
245     write(msgbuf,'(a)') ' '
246     call print_message( msgbuf, standardmessageunit,
247     & SQUEEZE_RIGHT , mythid)
248     #endif
249    
250     #else
251     c-- Do not enter the calculation of the drift contribution to
252     c-- the final cost function.
253    
254     _BEGIN_MASTER( mythid )
255     write(msgbuf,'(a)') ' '
256     call print_message( msgbuf, standardmessageunit,
257     & SQUEEZE_RIGHT , mythid)
258     write(msgbuf,'(a,a)')
259     & ' cost_Driftw: no contribution of drift between the first ',
260     & 'and the last year to cost function.'
261     call print_message( msgbuf, standardmessageunit,
262     & SQUEEZE_RIGHT , mythid)
263     write(msgbuf,'(a,a,i9.8)')
264     & ' cost_Driftw: number of records that would have',
265     & ' been processed: ',nmonsrec
266     call print_message( msgbuf, standardmessageunit,
267     & SQUEEZE_RIGHT , mythid)
268     write(msgbuf,'(a)') ' '
269     call print_message( msgbuf, standardmessageunit,
270     & SQUEEZE_RIGHT , mythid)
271     _END_MASTER( mythid )
272     #endif
273    
274     return
275     end
276    

  ViewVC Help
Powered by ViewVC 1.1.22