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

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

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


Revision 1.1 - (hide annotations) (download)
Thu Nov 6 22:10:07 2003 UTC (20 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint52l_pre, checkpoint52e_pre, hrcube4, checkpoint52n_post, checkpoint52j_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint52e_post, checkpoint53c_post, checkpoint55d_pre, checkpoint52j_pre, checkpoint54a_post, branch-netcdf, checkpoint52d_pre, checkpoint52l_post, checkpoint52k_post, checkpoint52b_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint53f_post, hrcube_1, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint54, checkpoint54f_post, checkpoint53b_post, checkpoint53, checkpoint52, checkpoint52d_post, checkpoint52a_post, checkpoint52b_post, checkpoint53g_post, checkpoint52f_post, checkpoint52c_post, ecco_c52_e35, hrcube5, checkpoint52a_pre, checkpoint52i_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint52i_pre, checkpoint51u_post, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3
Branch point for: netcdf-sm0
o merging from ecco-branch
o pkg/ecco now containes ecco-specific part of cost function
o top level routines the_main_loop, forward_step
  supersede those in model/src/
  previous input data.cost now in data.ecco
  (new namelist ecco_cost_nml)

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/cost/Attic/cost_ctds.F,v 1.1.2.4 2003/06/19 15:21:16 heimbach Exp $
2    
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_CTDS(
7     I myiter,
8     I mytime,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE cost_CTDS
14     c ==================================================================
15     c
16     c o Evaluate cost function contribution of CTD temperature data.
17     c
18     c started: Elisabeth Remy eremy@ucsd.edu 30-Aug-2000
19     c
20     c
21     c ==================================================================
22     c SUBROUTINE cost_CTDS
23     c ==================================================================
24    
25     implicit none
26    
27     c == global variables ==
28    
29     #include "EEPARAMS.h"
30     #include "SIZE.h"
31     #include "GRID.h"
32     #include "DYNVARS.h"
33    
34     #include "cal.h"
35     #include "ecco_cost.h"
36     #include "ctrl.h"
37     #include "ctrl_dummy.h"
38     #include "optim.h"
39    
40     c == routine arguments ==
41    
42     integer myiter
43     _RL mytime
44     integer mythid
45    
46     c == local variables ==
47    
48     integer bi,bj
49     integer i,j,k
50     integer itlo,ithi
51     integer jtlo,jthi
52     integer jmin,jmax
53     integer imin,imax
54     integer nrec
55     integer irec
56     integer ilu
57    
58     _RL fctile_ctds
59     _RL fcthread_ctds
60     _RL www (1-olx:snx+olx,1-oly:sny+oly)
61     _RL wtmp (1-olx:snx+olx,1-oly:sny+oly)
62     _RL tmpobs (1-olx:snx+olx,1-oly:sny+oly)
63     _RL tmpbar (1-olx:snx+olx,1-oly:sny+oly)
64     _RL spval
65    
66     character*(80) fnamesalt
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     cph merged from SIO
90     cph spval = -9990.
91     spval = -9.
92    
93     c-- Read state record from global file.
94     doglobalread = .false.
95     ladinit = .false.
96    
97     #ifdef ALLOW_CTDS_COST_CONTRIBUTION
98    
99     #ifdef ECCO_VERBOSE
100     write(msgbuf,'(a)') ' '
101     call print_message( msgbuf, standardmessageunit,
102     & SQUEEZE_RIGHT , mythid)
103     write(msgbuf,'(a,i8.8)')
104     & ' cost_CTDS: number of records to process =', nmonsrec
105     call print_message( msgbuf, standardmessageunit,
106     & SQUEEZE_RIGHT , mythid)
107     write(msgbuf,'(a)') ' '
108     call print_message( msgbuf, standardmessageunit,
109     & SQUEEZE_RIGHT , mythid)
110     #endif
111    
112     if (optimcycle .ge. 0) then
113     ilu=ilnblnk( sbarfile )
114     write(fnamesalt(1:80),'(2a,i10.10)')
115     & sbarfile(1:ilu), '.', optimcycle
116     endif
117    
118     fcthread_ctds = 0. _d 0
119    
120     c-- Loop over records.
121     do irec = 1,nmonsrec
122    
123     c-- Read time averages and the monthly mean data.
124     call active_read_xyz( fnamesalt, sbar, irec,
125     & doglobalread, ladinit,
126     & optimcycle, mythid, xx_sbar_mean_dummy )
127    
128     call mdsreadfield( ctdsfile, cost_iprec, 'RL', nr, ctdsobs,
129     & irec, mythid)
130    
131     c-- Loop over this thread's tiles.
132     do bj = jtlo,jthi
133     do bi = itlo,ithi
134     c-- Loop over the model layers
135    
136     fctile_ctds = 0. _d 0
137    
138     do k = 1,nr
139    
140     c-- Determine the weights to be used.
141     do j = jmin,jmax
142     do i = imin,imax
143     cph(
144     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
145     cph below statement could be replaced by following
146     cph to make it independnet of Nr:
147     cph
148     cph if ( rC(K) .GT. -1000. ) then
149     cph)
150     c set cmask=0 in areas shallower than 1000m
151     if ((ctdsobs(i,j,k,bi,bj) .ne. 0.).and.
152     & (ctdsobs(i,j,k,bi,bj) .gt. spval).and.
153     & (_hFacC(i,j,13,bi,bj) .ne. 0.).and.
154     & (_hFacC(i,j,k,bi,bj) .ne. 0.)) then
155     www(i,j) = cosphi(i,j,bi,bj)
156     tmpobs(i,j) = ctdsobs(i,j,k,bi,bj)
157     tmpbar(i,j) = sbar(i,j,k,bi,bj)
158     c wtmp(i,j) = wsalt(k,bi,bj)
159     wtmp(i,j) = wsalt2(i,j,k,bi,bj)
160    
161     fctile_ctds = fctile_ctds +
162     & (wtmp(i,j)*www(i,j))*
163     & (tmpbar(i,j)-tmpobs(i,j))*
164     & (tmpbar(i,j)-tmpobs(i,j))
165     endif
166     enddo
167     enddo
168     enddo
169     c-- End of loop over layers.
170    
171     fcthread_ctds = fcthread_ctds + fctile_ctds
172     objf_ctds(bi,bj) = objf_ctds(bi,bj) + fctile_ctds
173    
174     #ifdef ECCO_VERBOSE
175     write(msgbuf,'(a)') ' '
176     call print_message( msgbuf, standardmessageunit,
177     & SQUEEZE_RIGHT , mythid)
178     write(msgbuf,'(a,i8.8,1x,i3.3,1x,i3.3)')
179     & ' COST_CTDS: irec,bi,bj = ',irec,bi,bj
180     call print_message( msgbuf, standardmessageunit,
181     & SQUEEZE_RIGHT , mythid)
182     write(msgbuf,'(a,d22.15)')
183     & ' COST_CTDS: cost function = ', fctile_ctds
184     call print_message( msgbuf, standardmessageunit,
185     & SQUEEZE_RIGHT , mythid)
186     write(msgbuf,'(a)') ' '
187     call print_message( msgbuf, standardmessageunit,
188     & SQUEEZE_RIGHT , mythid)
189     #endif
190    
191     enddo
192     enddo
193    
194     #ifdef ECCO_VERBOSE
195     c-- Print cost function for all tiles.
196     _GLOBAL_SUM_R8( fcthread_ctds , myThid )
197     write(msgbuf,'(a)') ' '
198     call print_message( msgbuf, standardmessageunit,
199     & SQUEEZE_RIGHT , mythid)
200     write(msgbuf,'(a,i8.8)')
201     & ' cost_CTDS: irec = ',irec
202     call print_message( msgbuf, standardmessageunit,
203     & SQUEEZE_RIGHT , mythid)
204     write(msgbuf,'(a,a,d22.15)')
205     & ' global cost function value',
206     & ' ( CTD sal. ) = ',fcthread_ctds
207     call print_message( msgbuf, standardmessageunit,
208     & SQUEEZE_RIGHT , mythid)
209     write(msgbuf,'(a)') ' '
210     call print_message( msgbuf, standardmessageunit,
211     & SQUEEZE_RIGHT , mythid)
212     #endif
213    
214     enddo
215     c-- End of second loop over records.
216    
217     #else
218     c-- Do not enter the calculation of the CTD temperature contribution
219     c-- to the final cost function.
220    
221     fctile_ctds = 0. _d 0
222     fcthread_ctds = 0. _d 0
223    
224     crg
225     nrec = 1
226     crg
227    
228     _BEGIN_MASTER( mythid )
229     write(msgbuf,'(a)') ' '
230     call print_message( msgbuf, standardmessageunit,
231     & SQUEEZE_RIGHT , mythid)
232     write(msgbuf,'(a,a)')
233     & ' cost_CTDS: no contribution of CTD temperature ',
234     & ' to cost function.'
235     call print_message( msgbuf, standardmessageunit,
236     & SQUEEZE_RIGHT , mythid)
237     write(msgbuf,'(a,a,i9.8)')
238     & ' cost_CDTS: number of records that would have',
239     & ' been processed: ',nrec
240     call print_message( msgbuf, standardmessageunit,
241     & SQUEEZE_RIGHT , mythid)
242     write(msgbuf,'(a)') ' '
243     call print_message( msgbuf, standardmessageunit,
244     & SQUEEZE_RIGHT , mythid)
245     _END_MASTER( mythid )
246     #endif
247    
248     return
249     end

  ViewVC Help
Powered by ViewVC 1.1.22