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

Annotation of /MITgcm/pkg/ecco/cost_theta0.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: checkpoint57t_post, checkpoint57o_post, checkpoint57v_post, checkpoint57f_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint57i_post, checkpoint57m_post, checkpoint57g_pre, checkpoint57f_pre, checkpoint57r_post, checkpoint57h_done, checkpoint57n_post, checkpoint57p_post, checkpint57u_post, checkpoint57q_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post
Changes since 1.2: +3 -1 lines
Adding counters to cost terms.

1 heimbach 1.3 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_theta0.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_theta0(
7     I myiter,
8     I mytime,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE cost_zonstress
14     c ==================================================================
15     c
16     c o Calculate the zonal wind stress contribution to the cost function.
17     c
18     c started: Christian Eckert eckert@mit.edu 30-Jun-1999
19     c
20     c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
21     c
22     c - Restructured the code in order to create a package
23     c for the MITgcmUV.
24     c
25     c ==================================================================
26     c SUBROUTINE cost_zonstress
27     c ==================================================================
28    
29     implicit none
30    
31     c == global variables ==
32    
33     #include "EEPARAMS.h"
34     #include "SIZE.h"
35     #include "GRID.h"
36    
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     integer bi,bj
51     integer i,j,k
52     integer itlo,ithi
53     integer jtlo,jthi
54     integer jmin,jmax
55     integer imin,imax
56     integer nrec
57     integer irec
58     integer ilfld
59    
60     _RL fctile
61     _RL fcthread
62     _RL tmpx
63    
64     logical doglobalread
65     logical ladinit
66    
67     character*(80) fnamefld
68    
69     character*(MAX_LEN_MBUF) msgbuf
70    
71     c == external functions ==
72    
73     integer ilnblnk
74     external ilnblnk
75    
76     c == end of interface ==
77    
78     jtlo = mybylo(mythid)
79     jthi = mybyhi(mythid)
80     itlo = mybxlo(mythid)
81     ithi = mybxhi(mythid)
82     jmin = 1
83     jmax = sny
84     imin = 1
85     imax = snx
86    
87     c-- Read state record from global file.
88     doglobalread = .false.
89     ladinit = .false.
90    
91     irec = 1
92    
93     #ifdef ALLOW_THETA0_COST_CONTRIBUTION
94    
95     if (optimcycle .ge. 0) then
96     ilfld = ilnblnk( xx_theta_file )
97     write(fnamefld(1:80),'(2a,i10.10)')
98     & xx_theta_file(1:ilfld),'.',optimcycle
99     endif
100    
101     fcthread = 0. _d 0
102    
103     call active_read_xyz_loc( fnamefld, tmpfld3d, irec, doglobalread,
104     & ladinit, optimcycle, mythid
105     & , xx_theta_dummy )
106    
107     c-- Loop over this thread's tiles.
108     do bj = jtlo,jthi
109     do bi = itlo,ithi
110    
111     c-- Determine the weights to be used.
112    
113     fctile = 0. _d 0
114     do k = 1,nr
115     do j = jmin,jmax
116     do i = imin,imax
117     if (_hFacC(i,j,k,bi,bj) .ne. 0.) then
118     tmpx = tmpfld3d(i,j,k,bi,bj)
119 heimbach 1.2 if ( ABS(R_low(i,j,bi,bj)) .LT. 1000. )
120     & tmpx = tmpx*ABS(R_low(i,j,bi,bj))/1000.
121 heimbach 1.1 fctile = fctile
122     & + wtheta(k,bi,bj)*cosphi(i,j,bi,bj)
123     & *tmpx*tmpx
124 heimbach 1.3 if ( wtheta(k,bi,bj)*cosphi(i,j,bi,bj) .ne. 0. )
125     & num_temp0(bi,bj) = num_temp0(bi,bj) + 1. _d 0
126 heimbach 1.1 endif
127     enddo
128     enddo
129     enddo
130    
131     objf_temp0(bi,bj) = objf_temp0(bi,bj) + fctile
132     fcthread = fcthread + fctile
133    
134     #ifdef ECCO_VERBOSE
135     c-- Print cost function for each tile in each thread.
136     write(msgbuf,'(a)') ' '
137     call print_message( msgbuf, standardmessageunit,
138     & SQUEEZE_RIGHT , mythid)
139     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
140     & ' cost_theta0: irec,bi,bj = ',irec,bi,bj
141     call print_message( msgbuf, standardmessageunit,
142     & SQUEEZE_RIGHT , mythid)
143     write(msgbuf,'(a,d22.15)')
144     & ' cost function (dT(0)) = ',
145     & fctile
146     call print_message( msgbuf, standardmessageunit,
147     & SQUEEZE_RIGHT , mythid)
148     #endif
149     enddo
150     enddo
151    
152     #ifdef ECCO_VERBOSE
153     c-- Print cost function for all tiles.
154     _GLOBAL_SUM_R8( fcthread , myThid )
155     write(msgbuf,'(a)') ' '
156     call print_message( msgbuf, standardmessageunit,
157     & SQUEEZE_RIGHT , mythid)
158     write(msgbuf,'(a,i8.8)')
159     & ' cost_: irec = ',irec
160     call print_message( msgbuf, standardmessageunit,
161     & SQUEEZE_RIGHT , mythid)
162     write(msgbuf,'(a,d22.15)')
163     & ' global cost function value = ',
164     & fcthread
165     call print_message( msgbuf, standardmessageunit,
166     & SQUEEZE_RIGHT , mythid)
167     write(msgbuf,'(a)') ' '
168     call print_message( msgbuf, standardmessageunit,
169     & SQUEEZE_RIGHT , mythid)
170     #endif
171    
172     #else
173     c-- Do not enter the calculation of the salinity increment
174     c-- contribution to the final cost function.
175    
176     fctile = 0. _d 0
177     fcthread = 0. _d 0
178    
179     #ifdef ECCO_VERBOSE
180     _BEGIN_MASTER( mythid )
181     write(msgbuf,'(a)') ' '
182     call print_message( msgbuf, standardmessageunit,
183     & SQUEEZE_RIGHT , mythid)
184     write(msgbuf,'(a,a)')
185     & ' cost_theta0 : no contribution of the I.C. in salin. ',
186     & ' to cost function.'
187     call print_message( msgbuf, standardmessageunit,
188     & SQUEEZE_RIGHT , mythid)
189     write(msgbuf,'(a)') ' '
190     call print_message( msgbuf, standardmessageunit,
191     & SQUEEZE_RIGHT , mythid)
192     _END_MASTER( mythid )
193     #endif
194    
195     #endif
196    
197     return
198     end
199    
200    

  ViewVC Help
Powered by ViewVC 1.1.22