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

Contents of /MITgcm/pkg/ecco/cost_ssh_mean.F

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


Revision 1.5 - (show annotations) (download)
Fri May 27 22:10:26 2005 UTC (18 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint57s_post, checkpoint57k_post, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint57m_post, checkpoint58n_post, checkpoint58x_post, checkpoint58t_post, checkpoint58h_post, checkpoint58w_post, checkpoint57y_pre, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint58f_post, checkpoint57n_post, checkpoint58d_post, checkpoint58c_post, checkpoint57w_post, checkpoint57p_post, checkpint57u_post, checkpoint58a_post, checkpoint58i_post, checkpoint57q_post, checkpoint58o_post, checkpoint57z_post, checkpoint58y_post, checkpoint58k_post, checkpoint58v_post, checkpoint58s_post, checkpoint58p_post, checkpoint57j_post, checkpoint58b_post, checkpoint58m_post, checkpoint57l_post
Changes since 1.4: +14 -1 lines
o adding some cost transport diagnostics
o adding second set of flux weights whflux2, etc
o for mean SSH, read TOPEX mean first to compute effective mask

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_ssh_mean.F,v 1.4 2005/05/05 23:47:57 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_ssh_mean(
7 I psmean, offset
8 O , costmean
9 I , mythid
10 & )
11
12 c ==================================================================
13 c SUBROUTINE cost_ssh_mean
14 c ==================================================================
15 c
16 c o Evaluate cost function contribution of sea surface height.
17 c using of geoid error covariances requires regular model grid
18 c o TODO: interpolate model grid to regular grid
19 c check mask
20 c
21 c started: Detlef Stammer, Ralf Giering Jul-1996
22 c changed: Ralf Giering Ralf.Giering@FastOpt.de 12-Jun-2001
23 c - totally rewrite for parallel processing
24 c heimbach@mit.edu 13-Mar-2002
25 c - several wrong i-loop boundaries (spotted by G. Gebbie)
26 c - nprocs need to be replaced by nPx*nPy
27 c - geoid error does not work as of now
28 c heimbach@mit.edu 05-May-2005
29 c - debugged and restructuted
30 c
31 c ==================================================================
32 c SUBROUTINE cost_ssh_mean
33 c ==================================================================
34
35 implicit none
36
37 c == global variables ==
38
39 #include "EEPARAMS.h"
40 #include "SIZE.h"
41 #include "PARAMS.h"
42
43 #include "ecco_cost.h"
44 #include "optim.h"
45
46 #ifdef ALLOW_EGM96_ERROR_COV
47 # if (defined (ALLOW_USE_MPI) || defined (ALWAYS_USE_MPI))
48 # include "EESUPPORT.h"
49 # else
50 INTEGER nProcs
51 PARAMETER (nProcs=1)
52 # endif
53 # include "sphere.h"
54 #endif
55
56 c == routine arguments ==
57
58 _RL psmean ( 1-olx:snx+olx, 1-oly:sny+oly, nsx, nsy )
59 _RL offset
60 _RL costmean
61 integer mythid
62
63 c == local variables ==
64
65 integer bi,bj
66 integer i,j
67 integer itlo,ithi
68 integer jtlo,jthi
69 integer jmin,jmax
70 integer imin,imax
71
72 cph(
73 _RL diagnosfld(1-olx:snx+olx,1-oly:sny+oly,nsx,nsy)
74 cph)
75
76 #ifdef ALLOW_EGM96_ERROR_COV
77 _RL cphi
78 _RL xmean
79 _RL shc( ncshc )
80 _RL misfit ( 1-olx:snx+olx, 1-oly:sny+oly, nsx,nsy )
81 _RL misfitgl( 1-olx:snx+olx, 1-oly:sny+oly, nsx,nsy, npx,npy )
82
83 _RL pwork ( (lshcmax+1)*(lshcmax+2)/2 )
84 _RL diffearth ( lonshc, latshc )
85 integer joffset
86 integer ipx, ipy
87 integer iglobe, jglobe
88 integer iproc
89 integer mpirc
90 integer mpicrd(2)
91 #endif
92
93 _RL diff
94 Real*8 sumc
95 character*(max_len_mbuf) msgbuf
96
97 c == end of interface ==
98
99 c-- Initialise local variables.
100 jtlo = mybylo(mythid)
101 jthi = mybyhi(mythid)
102 itlo = mybxlo(mythid)
103 ithi = mybxhi(mythid)
104
105 jmin = 1
106 jmax = sny
107 imin = 1
108 imax = snx
109
110 costmean = 0.
111
112 #ifdef ALLOW_EGM96_ERROR_COV
113
114 c-- compute misfit on local domain
115 do bj = jtlo,jthi
116 do bi = itlo,ithi
117 do j = jmin,jmax
118 do i = imin,imax
119 if ( tpmeanmask(i,j,bi,bj) .gt. 0. ) then
120 misfit(i,j,bi,bj) =
121 & tpmean(i,j,bi,bj) - offset - psmean(i,j,bi,bj)
122 else
123 misfit(i,j,bi,bj) = 0.
124 endif
125 enddo
126 enddo
127 enddo
128 enddo
129
130 c-- communicate to get misfit on full 2d model surface grid
131 #if (defined (ALLOW_USE_MPI) || defined (ALWAYS_USE_MPI))
132 call exch_all_2d_rl( misfit, misfitgl, mythid )
133 #else
134 do bj = jtlo,jthi
135 do bi = itlo,ithi
136 do j = jmin,jmax
137 do i = imin,imax
138 misfitgl(i,j,bi,bj,1,1) = misfit(i,j,bi,bj)
139 enddo
140 enddo
141 enddo
142 enddo
143 #endif
144
145 c-- set meridional index offset,
146 c-- it is non zero if the grid does no reach the poles
147 joffset = (latshc - ny)/2
148
149 write(msgbuf,'(a,I10)')
150 & 'cost_ssh_mean: grid starts at point ', joffset
151 call print_message( msgbuf, standardmessageunit,
152 & SQUEEZE_RIGHT , mythid)
153
154 c-- preset field
155 c-- necessary if the grid does no reach the poles
156 do j = 1, latshc
157 do i = 1, lonshc
158 diffearth(i,j) = 0.
159 enddo
160 enddo
161
162 c-- -interpolate- from model grid to regular grid
163 c-- so far we assume that the model grid is already regular
164 _BEGIN_MASTER( mythid )
165
166 do iproc = 1, nprocs
167
168 #if (defined (ALLOW_USE_MPI) || defined (ALWAYS_USE_MPI))
169 c-- get coordinates of processor (iporc-1)
170 call MPI_Cart_coords(
171 I MPI_COMM_MODEL, iproc-1, 2, mpicrd
172 O , mpirc
173 & )
174 ipx = 1 + mpicrd(1)
175 ipy = 1 + mpicrd(2)
176 #else
177 ipx = 1
178 ipy = 1
179 #endif
180
181 do bj = jtlo,jthi
182 do bi = itlo,ithi
183
184 do j = jmin,jmax
185 do i = imin,imax
186 jglobe = joffset+ j + sNy*(bj-1) + sNy*nSy*(ipy-1)
187 iglobe = i + sNx*(bi-1) + sNx*nSx*(ipx-1)
188
189 diffearth(iglobe,jglobe) = misfitgl(i,j,bi,bj,ipx,ipy)
190 enddo
191 enddo
192
193 enddo
194 enddo
195
196 enddo
197
198 c-- Project regular grid misfit onto sperical harmonics
199 call shc4grid(
200 I lshcmax
201 O , shc
202 I , latshc, lonshc
203 I , diffearth
204 W , pwork
205 & )
206
207 c-- Remove the C(0,0) component, i.e. the global mean.
208 shc(1) = 0.
209
210 C-- Compute the cost function for the mean SSH.
211 call cost_geoid(
212 O costmean
213 I , shc
214 I , mythid
215 & )
216
217 _END_MASTER( mythid )
218
219 _BARRIER
220
221 #else
222
223 c-- Compute cost function for SSH by using the diagonal
224 c-- of the error covariance only.
225 c--
226 c-- Note: wp is assumed to include latitude dependence
227 c-- of error due to meridian convergence;
228 c-- --> no weighting by cosphi.
229
230 sumc = 0.
231 do bj = jtlo,jthi
232 do bi = itlo,ithi
233 do j = jmin,jmax
234 do i = imin,imax
235 diff = psmean(i,j,bi,bj) - tpmean(i,j,bi,bj) + offset
236 sumc = sumc + diff*diff
237 & * wp(i,j,bi,bj)*tpmeanmask(i,j,bi,bj)
238 if ( wp(i,j,bi,bj)*tpmeanmask(i,j,bi,bj) .ne. 0. )
239 & num_hmean = num_hmean + 1. _d 0
240 diagnosfld(i,j,bi,bj) = diff*diff
241 & * wp(i,j,bi,bj)*tpmeanmask(i,j,bi,bj)
242 enddo
243 enddo
244 enddo
245 enddo
246
247 cph(
248 CALL WRITE_FLD_XY_RL( 'DiagnosSSHmean', ' ', diagnosfld,
249 & optimcycle, mythid )
250 cph)
251
252 c-- Do the global summation.
253 _GLOBAL_SUM_R8( sumc, mythid )
254 _GLOBAL_SUM_R8( num_hmean, mythid )
255 costmean = sumc
256
257 #endif
258
259 end

  ViewVC Help
Powered by ViewVC 1.1.22