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

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

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


Revision 1.6 - (show annotations) (download)
Wed Jun 17 15:14:00 2009 UTC (14 years, 11 months ago) by heimbach
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, checkpoint61v, checkpoint61w, checkpoint61t, checkpoint61u, checkpoint61r, checkpoint61s, checkpoint61q, checkpoint61z, checkpoint61x, checkpoint61y
Changes since 1.5: +2 -10 lines
Reduce depth limit for altimetry to 200 m
(and make independent of vertical disctetization)

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_readgfo.F,v 1.5 2007/10/09 00:02:50 jmc Exp $
2 C $Name: $
3
4 #include "COST_CPPOPTIONS.h"
5
6
7 subroutine cost_readgfo( irec, mythid )
8
9 c ==================================================================
10 c SUBROUTINE cost_readgfo
11 c ==================================================================
12 c
13 c o Read a given record of the GFO SSH data.
14 c
15 c started: Christian Eckert eckert@mit.edu 25-May-1999
16 c
17 c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
18 c
19 c - Restructured the code in order to create a package
20 c for the MITgcmUV.
21 c
22 c ==================================================================
23 c SUBROUTINE cost_readgfo
24 c ==================================================================
25
26 implicit none
27
28 c == global variables ==
29
30 #include "EEPARAMS.h"
31 #include "SIZE.h"
32 #include "PARAMS.h"
33 #include "GRID.h"
34
35 #include "cal.h"
36 #include "ecco_cost.h"
37
38 c == routine arguments ==
39
40 integer irec
41 integer mythid
42
43 #ifdef ALLOW_SSH_GFOANOM_COST_CONTRIBUTION
44 c == local variables ==
45
46 integer bi,bj
47 integer i,j,k
48 integer itlo,ithi
49 integer jtlo,jthi
50 integer jmin,jmax
51 integer imin,imax
52 integer sshrec
53 integer difftime(4)
54 integer middate(4)
55 integer noffset
56 _RL diffsecs
57 _RL spval
58 _RL factor
59
60 cnew(
61 integer il
62 _RL daytime
63 integer dayiter
64 integer daydate(4)
65 integer yday, ymod
66 integer md, dd, sd, ld, wd
67 character*(80) fnametmp
68 logical exst
69 cnew)
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 factor = 0.01
88 spval = -9990.
89
90 cnew(
91 daytime = FLOAT(secondsperday*(irec-1)) + modelstart
92 dayiter = hoursperday*(irec-1)+modeliter0
93 call cal_getdate( dayiter, daytime, daydate, mythid )
94 call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
95 ymod = gfostartdate(1)/10000
96
97 if ( ymod .EQ. yday ) then
98 middate(1) = modelstartdate(1)
99 else
100 middate(1) = yday*10000+100+1
101 endif
102 middate(2) = 0
103 middate(3) = modelstartdate(3)
104 middate(4) = modelstartdate(4)
105
106 call cal_TimePassed( middate, daydate, difftime, mythid )
107 call cal_ToSeconds( difftime, diffsecs, mythid )
108 sshrec = int(diffsecs/gfoperiod) + 1
109
110 il=ilnblnk(gfofile)
111 write(fnametmp(1:80),'(2a,i4)')
112 & gfofile(1:il), '_', yday
113 inquire( file=fnametmp, exist=exst )
114 if (.NOT. exst) then
115 write(fnametmp(1:80),'(a)') gfofile(1:il)
116 sshrec = irec
117 endif
118
119 cnew)
120
121
122 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1, gfoobs,
123 & sshrec, mythid )
124
125
126 do bj = jtlo,jthi
127 do bi = itlo,ithi
128 k = 1
129 do j = jmin,jmax
130 do i = imin,imax
131 if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
132 gfomask(i,j,bi,bj) = 0. _d 0
133 else
134 gfomask(i,j,bi,bj) = 1. _d 0
135 endif
136 if (gfoobs(i,j,bi,bj) .le. spval) then
137 gfomask(i,j,bi,bj) = 0. _d 0
138 endif
139 if (abs(gfoobs(i,j,bi,bj)) .lt. 1.d-8 ) then
140 gfomask(i,j,bi,bj) = 0. _d 0
141 endif
142
143 if ( R_low(i,j,bi,bj) .GT. -200. ) then
144 gfomask(i,j,bi,bj) = 0. _d 0
145 endif
146
147 gfomask(i,j,bi,bj) = gfomask(i,j,bi,bj)*frame(i,j)
148 gfoobs(i,j,bi,bj) = gfomask(i,j,bi,bj)*factor*
149 & ( gfoobs(i,j,bi,bj) -
150 & ( gfointercept + gfoslope*irec*hoursperday ) )
151 enddo
152 enddo
153 enddo
154 enddo
155
156 #endif
157
158 return
159 end
160

  ViewVC Help
Powered by ViewVC 1.1.22