/[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.5 - (show annotations) (download)
Mon Mar 6 19:16:53 2006 UTC (18 years, 2 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58c_post, checkpoint58b_post
Changes since 1.4: +4 -4 lines
Remove trend in SSH anomaly obs.

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_readtopex.F,v 1.4 2006/02/15 20:01:51 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_readtopex( irec, mythid )
7
8 c ==================================================================
9 c SUBROUTINE cost_readtopex
10 c ==================================================================
11 c
12 c o Read a given record of the TOPEX SSH data.
13 c
14 c started: Christian Eckert eckert@mit.edu 25-May-1999
15 c
16 c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
17 c
18 c - Restructured the code in order to create a package
19 c for the MITgcmUV.
20 c
21 c ==================================================================
22 c SUBROUTINE cost_readtopex
23 c ==================================================================
24
25 implicit none
26
27 c == global variables ==
28
29 #include "EEPARAMS.h"
30 #include "SIZE.h"
31 #include "PARAMS.h"
32 #include "GRID.h"
33
34 #include "cal.h"
35 #include "ecco_cost.h"
36
37 c == routine arguments ==
38
39 integer irec
40 integer mythid
41
42 #ifdef ALLOW_SSH_TPANOM_COST_CONTRIBUTION
43 c == local variables ==
44
45 integer bi,bj
46 integer i,j,k
47 integer itlo,ithi
48 integer jtlo,jthi
49 integer jmin,jmax
50 integer imin,imax
51 integer sshrec
52 integer difftime(4)
53 integer middate(4)
54 integer noffset
55 _RL diffsecs
56 _RL spval
57 _RL factor
58
59 cnew(
60 integer il
61 _RL daytime
62 integer dayiter
63 integer daydate(4)
64 integer yday, ymod
65 integer md, dd, sd, ld, wd
66 character*(80) fnametmp
67 logical exst
68 cnew)
69
70 c == external functions ==
71
72 integer ilnblnk
73 external ilnblnk
74
75 c == end of interface ==
76
77 jtlo = mybylo(mythid)
78 jthi = mybyhi(mythid)
79 itlo = mybxlo(mythid)
80 ithi = mybxhi(mythid)
81 jmin = 1
82 jmax = sny
83 imin = 1
84 imax = snx
85
86 factor = 0.01
87 spval = -9990.
88
89 cnew(
90 daytime = FLOAT(secondsperday*(irec-1))
91 dayiter = hoursperday*(irec-1)
92 call cal_getdate( dayiter, daytime, daydate, mythid )
93 call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
94 ymod = topexstartdate(1)/10000
95
96 if ( ymod .EQ. yday ) then
97 middate(1) = modelstartdate(1)
98 else
99 middate(1) = yday*10000+100+1
100 endif
101 middate(2) = 0
102 middate(3) = modelstartdate(3)
103 middate(4) = modelstartdate(4)
104
105 call cal_TimePassed( middate, daydate, difftime, mythid )
106 call cal_ToSeconds( difftime, diffsecs, mythid )
107 sshrec = int(diffsecs/topexperiod) + 1
108
109 il=ilnblnk(topexfile)
110 write(fnametmp(1:80),'(2a,i4)')
111 & topexfile(1:il), '_', yday
112 inquire( file=fnametmp, exist=exst )
113 if (.NOT. exst) then
114 write(fnametmp(1:80),'(a)') topexfile(1:il)
115 sshrec = irec
116 endif
117
118 cnew)
119
120 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1, tpobs,
121 & sshrec, mythid )
122
123 do bj = jtlo,jthi
124 do bi = itlo,ithi
125 k = 1
126 do j = jmin,jmax
127 do i = imin,imax
128 if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
129 tpmask(i,j,bi,bj) = 0. _d 0
130 else
131 tpmask(i,j,bi,bj) = 1. _d 0
132 endif
133 if (tpobs(i,j,bi,bj) .le. spval) then
134 tpmask(i,j,bi,bj) = 0. _d 0
135 endif
136 if (abs(tpobs(i,j,bi,bj)) .lt. 1.d-8 ) then
137 tpmask(i,j,bi,bj) = 0. _d 0
138 endif
139
140 cph(
141 cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
142 cph below statement could be replaced by following
143 cph to make it independnet of Nr:
144 cph
145 cph if ( rC(K) .GT. -1000. ) then
146 cph)
147 c set tpmask=0 in areas shallower than 1000m
148 if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
149 tpmask(i,j,bi,bj) = 0. _d 0
150 endif
151
152 tpmask(i,j,bi,bj) = tpmask(i,j,bi,bj)*frame(i,j)
153 tpobs(i,j,bi,bj) = tpmask(i,j,bi,bj)*factor*
154 & ( tpobs(i,j,bi,bj) -
155 & ( topexintercept + topexslope*irec*hoursperday ) )
156 enddo
157 enddo
158 enddo
159 enddo
160
161 #endif /* ALLOW_SSH_TPANOM_COST_CONTRIBUTION */
162
163 return
164 end
165

  ViewVC Help
Powered by ViewVC 1.1.22