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

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

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


Revision 1.1 - (show annotations) (download)
Tue Nov 3 03:32:25 2009 UTC (14 years, 7 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint62, checkpoint63, checkpoint62c, checkpoint62b, checkpoint62a, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62d, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x, checkpoint61z, checkpoint61y
MDT/SLA cost function terms for ECCO version 4 -- initial check-in

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_sla_read.F,v 1.1 2009/06/17 15:14:00 gforget Exp $
2 C $Name: $
3
4 #include "COST_CPPOPTIONS.h"
5
6
7 subroutine cost_sla_read( sla_file, sla_startdate, sla_period,
8 I sla_intercept, sla_slope,
9 O sla_obs, sla_mask,
10 I irec, mythid )
11
12 c ==================================================================
13 c SUBROUTINE cost_sla_read
14 c ==================================================================
15 c
16 c o Read a given record of the SLA data.
17 c
18 c started: Gael Forget 20-Oct-2009
19 c
20 c ==================================================================
21 c SUBROUTINE cost_sla_read
22 c ==================================================================
23
24 implicit none
25
26 c == global variables ==
27
28 #include "EEPARAMS.h"
29 #include "SIZE.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32
33 #include "cal.h"
34 #include "ecco_cost.h"
35
36 c == routine arguments ==
37
38 integer irec
39 integer mythid
40
41 c == local variables ==
42
43 integer bi,bj
44 integer i,j,k
45 integer itlo,ithi
46 integer jtlo,jthi
47 integer jmin,jmax
48 integer imin,imax
49 integer sshrec
50 integer difftime(4)
51 integer middate(4)
52 integer noffset
53 _RL diffsecs
54 _RL spval
55 _RL factor
56
57 integer sla_startdate(4)
58 _RL sla_period
59 _RL sla_intercept
60 _RL sla_slope
61 _RL sla_obs (1-olx:snx+olx,1-oly:sny+oly, nsx,nsy)
62 _RL sla_mask (1-olx:snx+olx,1-oly:sny+oly, nsx,nsy)
63 character*(MAX_LEN_FNAM) sla_file
64
65 cnew(
66 integer il
67 _RL daytime
68 integer dayiter
69 integer daydate(4)
70 integer yday, ymod
71 integer md, dd, sd, ld, wd
72 character*(80) fnametmp
73 logical exst
74 cnew)
75
76 c == external functions ==
77
78 integer ilnblnk
79 external ilnblnk
80
81 c == end of interface ==
82
83 jtlo = mybylo(mythid)
84 jthi = mybyhi(mythid)
85 itlo = mybxlo(mythid)
86 ithi = mybxhi(mythid)
87 jmin = 1
88 jmax = sny
89 imin = 1
90 imax = snx
91
92 factor = 0.01
93 spval = -9990.
94
95 cnew(
96 daytime = FLOAT(secondsperday*(irec-1)) + modelstart
97 dayiter = hoursperday*(irec-1)+modeliter0
98 call cal_getdate( dayiter, daytime, daydate, mythid )
99 call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
100 ymod = sla_startdate(1)/10000
101
102 if ( ymod .EQ. yday ) then
103 middate(1) = modelstartdate(1)
104 else
105 middate(1) = yday*10000+100+1
106 endif
107 middate(2) = 0
108 middate(3) = modelstartdate(3)
109 middate(4) = modelstartdate(4)
110
111 call cal_TimePassed( middate, daydate, difftime, mythid )
112 call cal_ToSeconds( difftime, diffsecs, mythid )
113 sshrec = int(diffsecs/sla_period) + 1
114
115 il=ilnblnk(sla_file)
116 write(fnametmp(1:80),'(2a,i4)')
117 & sla_file(1:il), '_', yday
118 inquire( file=fnametmp, exist=exst )
119 if (.NOT. exst) then
120 write(fnametmp(1:80),'(a)') sla_file(1:il)
121 sshrec = irec
122 endif
123
124 cnew)
125
126
127 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1, sla_obs,
128 & sshrec, mythid )
129
130
131 do bj = jtlo,jthi
132 do bi = itlo,ithi
133 k = 1
134 do j = jmin,jmax
135 do i = imin,imax
136 if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
137 sla_mask(i,j,bi,bj) = 0. _d 0
138 else
139 sla_mask(i,j,bi,bj) = 1. _d 0
140 endif
141 if (sla_obs(i,j,bi,bj) .le. spval) then
142 sla_mask(i,j,bi,bj) = 0. _d 0
143 endif
144 if (abs(sla_obs(i,j,bi,bj)) .lt. 1.d-8 ) then
145 sla_mask(i,j,bi,bj) = 0. _d 0
146 endif
147
148 cph(
149 if ( R_low(i,j,bi,bj) .GT. -200. ) then
150 sla_mask(i,j,bi,bj) = 0. _d 0
151 endif
152 cph)
153
154 sla_mask(i,j,bi,bj) = sla_mask(i,j,bi,bj)*frame(i,j)
155 sla_obs(i,j,bi,bj) = sla_mask(i,j,bi,bj)*factor*
156 & ( sla_obs(i,j,bi,bj) -
157 & ( sla_intercept + sla_slope*irec*hoursperday ) )
158 enddo
159 enddo
160 enddo
161 enddo
162
163
164 return
165 end
166

  ViewVC Help
Powered by ViewVC 1.1.22