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

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

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


Revision 1.5 - (show annotations) (download)
Wed Jun 17 15:12:53 2009 UTC (14 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: 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.4: +1 -3 lines
Remove depth limitations.

1 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_readscatyfields.F,v 1.4 2007/10/09 00:02:50 jmc Exp $
2 C $Name: $
3
4 #include "COST_CPPOPTIONS.h"
5
6
7 subroutine cost_ReadscatyFields(
8 I irec,
9 I mythid
10 & )
11
12 c ==================================================================
13 c SUBROUTINE cost_ReadscatyFields
14 c ==================================================================
15 c
16 c o Read a given record of the SST data.
17 c
18 c started: Christian Eckert eckert@mit.edu 25-May-1999
19 c
20 c changed: Christian Eckert eckert@mit.edu 25-Feb-2000
21 c
22 c - Restructured the code in order to create a package
23 c for the MITgcmUV.
24 c
25 c ==================================================================
26 c SUBROUTINE cost_ReadscatyFields
27 c ==================================================================
28
29 implicit none
30
31 c == global variables ==
32
33 #include "EEPARAMS.h"
34 #include "SIZE.h"
35 #include "PARAMS.h"
36 #include "GRID.h"
37
38 #include "cal.h"
39 #include "ecco_cost.h"
40
41 c == routine arguments ==
42
43 integer irec
44 integer mythid
45
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 nobs
55 integer scatyrec
56 integer beginscaty
57 integer beginrun
58
59 _RL spval
60 _RL vartile
61
62 cnew(
63 integer il
64 integer mody, modm
65 integer iyear, imonth
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 parameter (spval = -1.8 )
78 ce --> there is certainly a better place for this.
79
80 jtlo = mybylo(mythid)
81 jthi = mybyhi(mythid)
82 itlo = mybxlo(mythid)
83 ithi = mybxhi(mythid)
84 jmin = 1
85 jmax = sny
86 imin = 1
87 imax = snx
88
89 c beginscaty = scatystartdate(1)/10000
90 c beginrun = modelstartdate(1)/10000
91 c if ( beginscaty .eq. beginrun ) then
92 c scatyrec = mod(modelstartdate(1)/100,100) -
93 c & mod(scatystartdate(1)/100,100) + irec
94 c else
95 c scatyrec = ( beginrun - beginscaty - 1)*nmonthyear +
96 c & (nmonthyear - mod(scatystartdate(1)/100,100) +
97 c & 1) + mod(modelstartdate(1)/100,100) - 1 + irec
98 c endif
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(scatydatfile)
107 write(fnametmp(1:80),'(2a,i4)')
108 & scatydatfile(1:il), '_', iyear
109 inquire( file=fnametmp, exist=exst )
110 if (.NOT. exst) then
111 write(fnametmp(1:80),'(a)') scatydatfile(1:il)
112 imonth = irec
113 endif
114
115 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1,
116 & scatydat, imonth, mythid )
117 cnew)
118
119 nobs = 0
120 do bj = jtlo,jthi
121 do bi = itlo,ithi
122 k = 1
123 do j = jmin,jmax
124 do i = imin,imax
125 if (maskS(i,j,k,bi,bj) .eq. 0.) then
126 scatymask(i,j,bi,bj) = 0. _d 0
127 else
128 scatymask(i,j,bi,bj) = 1. _d 0
129 endif
130 if (scatydat(i,j,bi,bj) .lt. spval) then
131 scatymask(i,j,bi,bj) = 0. _d 0
132 endif
133 if (scatydat(i,j,bi,bj) .eq. 0. _d 0 ) then
134 scatymask(i,j,bi,bj) = 0. _d 0
135 endif
136 scatymask(i,j,bi,bj) = scatymask(i,j,bi,bj)*frame(i,j)
137 scatydat(i,j,bi,bj) = scatydat(i,j,bi,bj)*
138 & scatymask(i,j,bi,bj)
139 nobs = nobs + int(scatymask(i,j,bi,bj))
140 enddo
141 enddo
142 enddo
143 enddo
144
145 c-- Calculate the field variance for present subdomain.
146 c-- One could of course do a global sum here.
147 vartile = 0. _d 0
148 do bj = jtlo,jthi
149 do bi = itlo,ithi
150 do j = jmin,jmax
151 do i = imin,imax
152 vartile=vartile+scatydat(i,j,bi,bj)*scatydat(i,j,bi,bj)
153 enddo
154 enddo
155 enddo
156 enddo
157
158 if (nobs .gt. 0) then
159 vartile = vartile/float(nobs)
160 else
161 vartile = spval
162 endif
163
164 return
165 end
166

  ViewVC Help
Powered by ViewVC 1.1.22