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

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

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


Revision 1.2 - (show annotations) (download)
Mon Oct 11 16:38:53 2004 UTC (19 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57b_post, checkpoint57c_pre, checkpoint55j_post, checkpoint56b_post, checkpoint55h_post, checkpoint57e_post, checkpoint56c_post, checkpoint57a_post, checkpoint55g_post, checkpoint55f_post, checkpoint57a_pre, checkpoint55i_post, checkpoint57, checkpoint56, eckpoint57e_pre, checkpoint57c_post, checkpoint55e_post, checkpoint56a_post, checkpoint55d_post
Changes since 1.1: +47 -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 C $Header: /u/gcmpack/MITgcm/pkg/cost/Attic/cost_readtopex.F,v 1.1.2.2 2002/04/04 10:58:59 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_ReadTopex(
7 I irec,
8 I mythid
9 & )
10
11 c ==================================================================
12 c SUBROUTINE cost_ReadTopex
13 c ==================================================================
14 c
15 c o Read a given record of the TOPEX SSH data.
16 c
17 c started: Christian Eckert eckert@mit.edu 25-May-1999
18 c
19 c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
20 c
21 c - Restructured the code in order to create a package
22 c for the MITgcmUV.
23 c
24 c ==================================================================
25 c SUBROUTINE cost_ReadTopex
26 c ==================================================================
27
28 implicit none
29
30 c == global variables ==
31
32 #include "EEPARAMS.h"
33 #include "SIZE.h"
34 #include "PARAMS.h"
35 #include "GRID.h"
36
37 #include "cal.h"
38 #include "ecco_cost.h"
39
40 c == routine arguments ==
41
42 integer irec
43 integer mythid
44
45 #ifdef ALLOW_SSH_TPANOM_COST_CONTRIBUTION
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 sshrec
55 integer nobs
56 integer difftime(4)
57 integer middate(4)
58 integer noffset
59 _RL diffsecs
60 _RL spval
61 _RL factor
62 _RL vartile
63
64 cnew(
65 integer il
66 _RL daytime
67 integer dayiter
68 integer daydate(4)
69 integer yday, ymod
70 integer md, dd, sd, ld, wd
71 character*(80) fnametmp
72 logical exst
73 cnew)
74
75 c == external functions ==
76
77 integer ilnblnk
78 external ilnblnk
79
80 c == end of interface ==
81
82 jtlo = mybylo(mythid)
83 jthi = mybyhi(mythid)
84 itlo = mybxlo(mythid)
85 ithi = mybxhi(mythid)
86 jmin = 1
87 jmax = sny
88 imin = 1
89 imax = snx
90
91 factor = 0.01
92 spval = -9990.
93
94 cnew(
95 daytime = FLOAT(secondsperday*(irec-1))
96 dayiter = hoursperday*(irec-1)
97 call cal_getdate( dayiter, daytime, daydate, mythid )
98 call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
99 ymod = topexstartdate(1)/10000
100
101 if ( ymod .EQ. yday ) then
102 middate(1) = modelstartdate(1)
103 else
104 middate(1) = yday*10000+100+1
105 endif
106 middate(2) = 0
107 middate(3) = modelstartdate(3)
108 middate(4) = modelstartdate(4)
109
110 call cal_TimePassed( middate, daydate, difftime, mythid )
111 call cal_ToSeconds( difftime, diffsecs, mythid )
112 sshrec = int(diffsecs/topexperiod) + 1
113
114 il=ilnblnk(topexfile)
115 write(fnametmp(1:80),'(2a,i4)')
116 & topexfile(1:il), '_', yday
117 inquire( file=fnametmp, exist=exst )
118 if (.NOT. exst) then
119 write(fnametmp(1:80),'(a)') topexfile(1:il)
120 sshrec = irec
121 endif
122
123 print *, 'ph-ssh-topex ', irec, sshrec, ymod, yday
124 print *, 'ph-ssh-topex ', fnametmp
125 cnew)
126
127 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1, tpobs,
128 & sshrec, mythid )
129
130 nobs = 0
131
132 do bj = jtlo,jthi
133 do bi = itlo,ithi
134 k = 1
135 do j = jmin,jmax
136 do i = imin,imax
137 if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
138 tpmask(i,j,bi,bj) = 0. _d 0
139 else
140 tpmask(i,j,bi,bj) = 1. _d 0
141 endif
142 if (tpobs(i,j,bi,bj) .le. spval) then
143 tpmask(i,j,bi,bj) = 0. _d 0
144 endif
145 if (abs(tpobs(i,j,bi,bj)) .lt. 1.d-8 ) then
146 tpmask(i,j,bi,bj) = 0. _d 0
147 endif
148
149 cph(
150 cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
151 cph below statement could be replaced by following
152 cph to make it independnet of Nr:
153 cph
154 cph if ( rC(K) .GT. -1000. ) then
155 cph)
156 c set tpmask=0 in areas shallower than 1000m
157 if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
158 tpmask(i,j,bi,bj) = 0. _d 0
159 endif
160
161 tpmask(i,j,bi,bj) = tpmask(i,j,bi,bj)*frame(i,j)
162 tpobs(i,j,bi,bj) = tpobs(i,j,bi,bj)*
163 & tpmask(i,j,bi,bj)*
164 & factor
165 nobs = nobs + int(tpmask(i,j,bi,bj))
166 enddo
167 enddo
168 enddo
169 enddo
170
171 c-- Calculate the field variance for present subdomain.
172 c-- One could of course do a global sum here.
173 vartile = 0. _d 0
174 do bj = jtlo,jthi
175 do bi = itlo,ithi
176 do j = jmin,jmax
177 do i = imin,imax
178 vartile = vartile + tpobs(i,j,bi,bj)*
179 & tpobs(i,j,bi,bj)
180 enddo
181 enddo
182 enddo
183 enddo
184
185 if (nobs .gt. 0) then
186 vartile = vartile/float(nobs)
187 else
188 vartile = spval
189 endif
190
191 #endif /* ALLOW_SSH_TPANOM_COST_CONTRIBUTION */
192
193 return
194 end
195

  ViewVC Help
Powered by ViewVC 1.1.22