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

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

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


Revision 1.3 - (show annotations) (download)
Mon Mar 28 19:40:59 2005 UTC (19 years, 3 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58l_post, checkpoint57t_post, checkpoint57o_post, checkpoint58e_post, checkpoint57v_post, checkpoint58u_post, checkpoint57f_post, checkpoint57s_post, checkpoint57k_post, checkpoint57g_post, checkpoint58r_post, checkpoint57i_post, checkpoint57y_post, checkpoint58g_post, checkpoint57x_post, checkpoint57m_post, checkpoint58n_post, checkpoint58x_post, checkpoint57g_pre, checkpoint58t_post, checkpoint58h_post, checkpoint58w_post, checkpoint57y_pre, checkpoint57f_pre, checkpoint58q_post, checkpoint58j_post, checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint59h, checkpoint57r_post, checkpoint59, checkpoint58, checkpoint57h_done, 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, checkpoint57h_pre, checkpoint58m_post, checkpoint57l_post, checkpoint57h_post
Changes since 1.2: +1 -3 lines
Updating ECCO package
o clean up some masks to avoid dependencies
o add some crude limiters
o remove some print * output

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_readscatxfields.F,v 1.2 2004/10/11 16:38:53 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_ReadscatxFields(
7 I irec,
8 I mythid
9 & )
10
11 c ==================================================================
12 c SUBROUTINE cost_ReadscatxFields
13 c ==================================================================
14 c
15 c o Read a given record of the SST 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_ReadscatxFields
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 c == local variables ==
46
47 integer bi,bj
48 integer i,j,k
49 integer itlo,ithi
50 integer jtlo,jthi
51 integer jmin,jmax
52 integer imin,imax
53 integer nobs
54 integer scatxrec
55 integer beginscatx
56 integer beginrun
57
58 _RL spval
59 _RL vartile
60
61 cnew(
62 integer il
63 integer mody, modm
64 integer iyear, imonth
65 character*(80) fnametmp
66 logical exst
67 cnew)
68
69 c == external functions ==
70
71 integer ilnblnk
72 external ilnblnk
73
74 c == end of interface ==
75
76 parameter (spval = -1.8 )
77 ce --> there is certainly a better place for this.
78
79 jtlo = mybylo(mythid)
80 jthi = mybyhi(mythid)
81 itlo = mybxlo(mythid)
82 ithi = mybxhi(mythid)
83 jmin = 1
84 jmax = sny
85 imin = 1
86 imax = snx
87
88 c beginscatx = scatxstartdate(1)/10000
89 c beginrun = modelstartdate(1)/10000
90 c if ( beginscatx .eq. beginrun ) then
91 c scatxrec = mod(modelstartdate(1)/100,100) -
92 c & mod(scatxstartdate(1)/100,100) + irec
93 c else
94 c scatxrec = ( beginrun - beginscatx - 1)*nmonthyear +
95 c & (nmonthyear - mod(scatxstartdate(1)/100,100) +
96 c & 1) + mod(modelstartdate(1)/100,100) - 1 + irec
97 c endif
98
99
100 cnew(
101 mody = modelstartdate(1)/10000
102 modm = modelstartdate(1)/100 - mody*100
103 iyear = mody + INT((modm-1+irec-1)/12)
104 imonth = 1 + MOD(modm-1+irec-1,12)
105
106 il=ilnblnk(scatxdatfile)
107 write(fnametmp(1:80),'(2a,i4)')
108 & scatxdatfile(1:il), '_', iyear
109 inquire( file=fnametmp, exist=exst )
110 if (.NOT. exst) then
111 write(fnametmp(1:80),'(a)') scatxdatfile(1:il)
112 imonth = irec
113 endif
114
115 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1,
116 & scatxdat, imonth, mythid )
117 cnew)
118
119 nobs = 0
120
121 do bj = jtlo,jthi
122 do bi = itlo,ithi
123 k = 1
124 do j = jmin,jmax
125 do i = imin,imax
126 if (maskW(i,j,k,bi,bj) .eq. 0.) then
127 scatxmask(i,j,bi,bj) = 0. _d 0
128 else if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
129 scatxmask(i,j,bi,bj) = 0. _d 0
130 else
131 scatxmask(i,j,bi,bj) = 1. _d 0
132 endif
133 if (scatxdat(i,j,bi,bj) .lt. spval) then
134 scatxmask(i,j,bi,bj) = 0. _d 0
135 endif
136 if (scatxdat(i,j,bi,bj) .eq. 0. _d 0 ) then
137 scatxmask(i,j,bi,bj) = 0. _d 0
138 endif
139 scatxmask(i,j,bi,bj) = scatxmask(i,j,bi,bj)*frame(i,j)
140 scatxdat(i,j,bi,bj) = scatxdat(i,j,bi,bj)*
141 & scatxmask(i,j,bi,bj)
142 nobs = nobs + int(scatxmask(i,j,bi,bj))
143 enddo
144 enddo
145 enddo
146 enddo
147
148 c-- Calculate the field variance for present subdomain.
149 c-- One could of course do a global sum here.
150 vartile = 0. _d 0
151 do bj = jtlo,jthi
152 do bi = itlo,ithi
153 do j = jmin,jmax
154 do i = imin,imax
155 vartile=vartile+scatxdat(i,j,bi,bj)*scatxdat(i,j,bi,bj)
156 enddo
157 enddo
158 enddo
159 enddo
160
161 if (nobs .gt. 0) then
162 vartile = vartile/float(nobs)
163 else
164 vartile = spval
165 endif
166
167 return
168 end
169

  ViewVC Help
Powered by ViewVC 1.1.22