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

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

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


Revision 1.2 - (hide annotations) (download)
Mon Oct 11 16:38:53 2004 UTC (19 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57t_post, checkpoint57o_post, checkpoint57v_post, checkpoint57f_post, checkpoint57s_post, checkpoint57k_post, checkpoint57d_post, checkpoint57g_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint57i_post, checkpoint57y_post, checkpoint57x_post, checkpoint57m_post, checkpoint55h_post, checkpoint57g_pre, checkpoint57e_post, checkpoint56c_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint57a_post, checkpoint55g_post, checkpoint55f_post, checkpoint57r_post, checkpoint58, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57h_done, checkpoint57n_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint57q_post, checkpoint57z_post, checkpoint57c_post, checkpoint55e_post, checkpoint57j_post, checkpoint57h_pre, checkpoint57l_post, checkpoint57h_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.1: +5 -20 lines
o ECCO specific cost function terms (up-to-date with 1x1 runs)
o ecco_cost_weights is modified to 1x1 runs
o modifs to allow observations to be read in as
  single file or yearly files

1 heimbach 1.1
2     #include "COST_CPPOPTIONS.h"
3    
4    
5     subroutine cost_mean_saltflux(
6     I myiter,
7     I mytime,
8     I mythid
9     & )
10    
11     c ==================================================================
12     c SUBROUTINE cost_mean_saltflux
13     c ==================================================================
14     c
15     c o Evaluate cost function contribution of sea surface salinity.
16     c
17     c started: Elisabeth Remy 19-mar-2001 copy from cost_sst.F
18     c
19     c ==================================================================
20     c SUBROUTINE cost_mean_saltflux
21     c ==================================================================
22    
23     implicit none
24    
25     c == global variables ==
26    
27     #include "EEPARAMS.h"
28     #include "SIZE.h"
29     #include "GRID.h"
30     #include "DYNVARS.h"
31     #include "PARAMS.h"
32    
33     #include "cal.h"
34     #include "ecco_cost.h"
35     #include "ctrl.h"
36     #include "ctrl_dummy.h"
37     #include "optim.h"
38    
39     c == routine arguments ==
40    
41     integer myiter
42     _RL mytime
43     integer mythid
44    
45     c == local variables ==
46    
47     integer bi,bj
48 heimbach 1.2 integer i,j,kk
49 heimbach 1.1 integer itlo,ithi
50     integer jtlo,jthi
51     integer jmin,jmax
52     integer imin,imax
53     integer irec
54     integer levmon
55     integer levoff
56     integer ilsalt
57    
58     _RL fctilemm
59     _RL fcthreadmm
60     _RL tmpx
61     _RL sumcos
62    
63    
64     character*(80) fnamesflux
65    
66     logical doglobalread
67     logical ladinit
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 tiled data.
88     doglobalread = .false.
89     ladinit = .false.
90    
91     #ifdef ALLOW_MEAN_SFLUX_COST_CONTRIBUTION
92    
93     if (optimcycle .ge. 0) then
94     ilsalt = ilnblnk( sfluxbarfile )
95     write(fnamesflux(1:80),'(2a,i10.10)')
96     & sfluxbarfile(1:ilsalt),'.',optimcycle
97     endif
98    
99     fcthreadmm = 0. _d 0
100    
101     irec = 1
102    
103     c-- Read time averages and the monthly mean data.
104     call active_read_xy( fnamesflux, tmpfld2d, irec,
105     & doglobalread, ladinit,
106     & optimcycle, mythid,
107     & xx_sflux_mean_dummy )
108    
109     do bj = jtlo,jthi
110     do bi = itlo,ithi
111     kk = 1
112     fctilemm = 0. _d 0
113     sumcos = 0. _d 0
114     do j = jmin,jmax
115     do i = imin,imax
116     tmpx=tmpfld2d(i,j,bi,bj)
117 heimbach 1.2 if (maskC(i,j,kk,bi,bj) .ne. 0.) then
118     fctilemm = fctilemm+tmpx*cos(yc(i,j,bi,bj)*deg2rad)
119 heimbach 1.1 sumcos = sumcos + cos(yc(i,j,bi,bj)*deg2rad)
120     endif
121     enddo
122     enddo
123    
124 heimbach 1.2 if(sumcos.eq.0) sumcos=1.0
125 heimbach 1.1 fctilemm = (fctilemm / sumcos)
126 heimbach 1.2 fctilemm = wsfluxmm(bi,bj) * (fctilemm )
127 heimbach 1.1
128     objf_sfluxmm(bi,bj) = fctilemm
129     fcthreadmm = fcthreadmm + fctilemm
130    
131     #ifdef ECCO_VERBOSE
132     c-- Print cost function for all tiles.
133     _GLOBAL_SUM_R8( fcthreadmm , myThid )
134     write(msgbuf,'(a)') ' '
135     call print_message( msgbuf, standardmessageunit,
136     & SQUEEZE_RIGHT , mythid)
137     write(msgbuf,'(a,i8.8)')
138     & ' cost_saltflux: irec = ',irec
139     call print_message( msgbuf, standardmessageunit,
140     & SQUEEZE_RIGHT , mythid)
141     write(msgbuf,'(a,d22.15)')
142     & ' global cost function value = ',
143     & fcthreadmm
144     call print_message( msgbuf, standardmessageunit,
145     & SQUEEZE_RIGHT , mythid)
146     write(msgbuf,'(a)') ' '
147     call print_message( msgbuf, standardmessageunit,
148     & SQUEEZE_RIGHT , mythid)
149     #endif
150    
151     enddo
152     enddo
153    
154    
155     #ifdef ECCO_VERBOSE
156     c-- Print cost function for all tiles.
157     _GLOBAL_SUM_R8( fcthreadmm , myThid )
158     write(msgbuf,'(a)') ' '
159     call print_message( msgbuf, standardmessageunit,
160     & SQUEEZE_RIGHT , mythid)
161     write(msgbuf,'(a,i8.8)')
162     & ' cost_: irec = ',irec
163     call print_message( msgbuf, standardmessageunit,
164     & SQUEEZE_RIGHT , mythid)
165     write(msgbuf,'(a,a,d22.15)')
166     & ' global cost function value',
167     & ' ( ) = ',fcthreadmm
168     call print_message( msgbuf, standardmessageunit,
169     & SQUEEZE_RIGHT , mythid)
170     write(msgbuf,'(a)') ' '
171     call print_message( msgbuf, standardmessageunit,
172     & SQUEEZE_RIGHT , mythid)
173     #endif
174    
175     #else
176     c-- Do not enter the calculation of the temperature contribution to
177     c-- the final cost function.
178    
179     fctilemm = 0. _d 0
180     fcthreadmm = 0. _d 0
181    
182     _BEGIN_MASTER( mythid )
183     write(msgbuf,'(a)') ' '
184     call print_message( msgbuf, standardmessageunit,
185     & SQUEEZE_RIGHT , mythid)
186     write(msgbuf,'(a,a)')
187     & ' cost_: no contribution of temperature field ',
188     & 'to cost function.'
189     call print_message( msgbuf, standardmessageunit,
190     & SQUEEZE_RIGHT , mythid)
191     write(msgbuf,'(a,a,i9.8)')
192     & ' cost_: number of records that would have',
193     & ' been processed: ',nmonsrec
194     call print_message( msgbuf, standardmessageunit,
195     & SQUEEZE_RIGHT , mythid)
196     write(msgbuf,'(a)') ' '
197     call print_message( msgbuf, standardmessageunit,
198     & SQUEEZE_RIGHT , mythid)
199     _END_MASTER( mythid )
200     #endif
201    
202     return
203     end
204    

  ViewVC Help
Powered by ViewVC 1.1.22