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

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

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


Revision 1.5 - (hide annotations) (download)
Wed Jun 17 15:12:53 2009 UTC (15 years 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 heimbach 1.5 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_readscatxfields.F,v 1.4 2007/10/09 00:02:50 jmc Exp $
2 jmc 1.4 C $Name: $
3 heimbach 1.1
4     #include "COST_CPPOPTIONS.h"
5    
6    
7     subroutine cost_ReadscatxFields(
8     I irec,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE cost_ReadscatxFields
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_ReadscatxFields
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 jmc 1.4 integer mythid
45 heimbach 1.1
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 scatxrec
56     integer beginscatx
57     integer beginrun
58    
59     _RL spval
60     _RL vartile
61    
62 heimbach 1.2 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 jmc 1.4
72 heimbach 1.2 integer ilnblnk
73     external ilnblnk
74    
75 heimbach 1.1 c == end of interface ==
76    
77 jmc 1.4 parameter (spval = -1.8 )
78 heimbach 1.1 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 heimbach 1.2 c beginscatx = scatxstartdate(1)/10000
90     c beginrun = modelstartdate(1)/10000
91     c if ( beginscatx .eq. beginrun ) then
92     c scatxrec = mod(modelstartdate(1)/100,100) -
93     c & mod(scatxstartdate(1)/100,100) + irec
94     c else
95     c scatxrec = ( beginrun - beginscatx - 1)*nmonthyear +
96     c & (nmonthyear - mod(scatxstartdate(1)/100,100) +
97     c & 1) + mod(modelstartdate(1)/100,100) - 1 + irec
98     c endif
99    
100    
101     cnew(
102     mody = modelstartdate(1)/10000
103     modm = modelstartdate(1)/100 - mody*100
104     iyear = mody + INT((modm-1+irec-1)/12)
105     imonth = 1 + MOD(modm-1+irec-1,12)
106    
107     il=ilnblnk(scatxdatfile)
108 jmc 1.4 write(fnametmp(1:80),'(2a,i4)')
109 heimbach 1.2 & scatxdatfile(1:il), '_', iyear
110     inquire( file=fnametmp, exist=exst )
111     if (.NOT. exst) then
112     write(fnametmp(1:80),'(a)') scatxdatfile(1:il)
113     imonth = irec
114 heimbach 1.1 endif
115    
116 heimbach 1.2 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1,
117     & scatxdat, imonth, mythid )
118     cnew)
119 heimbach 1.1
120     nobs = 0
121 heimbach 1.2
122 heimbach 1.1 do bj = jtlo,jthi
123     do bi = itlo,ithi
124     k = 1
125     do j = jmin,jmax
126     do i = imin,imax
127 heimbach 1.2 if (maskW(i,j,k,bi,bj) .eq. 0.) then
128 heimbach 1.1 scatxmask(i,j,bi,bj) = 0. _d 0
129     else
130     scatxmask(i,j,bi,bj) = 1. _d 0
131     endif
132     if (scatxdat(i,j,bi,bj) .lt. spval) then
133     scatxmask(i,j,bi,bj) = 0. _d 0
134     endif
135     if (scatxdat(i,j,bi,bj) .eq. 0. _d 0 ) then
136     scatxmask(i,j,bi,bj) = 0. _d 0
137     endif
138     scatxmask(i,j,bi,bj) = scatxmask(i,j,bi,bj)*frame(i,j)
139     scatxdat(i,j,bi,bj) = scatxdat(i,j,bi,bj)*
140     & scatxmask(i,j,bi,bj)
141     nobs = nobs + int(scatxmask(i,j,bi,bj))
142     enddo
143     enddo
144     enddo
145     enddo
146    
147     c-- Calculate the field variance for present subdomain.
148     c-- One could of course do a global sum here.
149     vartile = 0. _d 0
150     do bj = jtlo,jthi
151     do bi = itlo,ithi
152     do j = jmin,jmax
153     do i = imin,imax
154     vartile=vartile+scatxdat(i,j,bi,bj)*scatxdat(i,j,bi,bj)
155     enddo
156     enddo
157     enddo
158     enddo
159    
160     if (nobs .gt. 0) then
161     vartile = vartile/float(nobs)
162     else
163     vartile = spval
164     endif
165    
166     return
167     end
168    

  ViewVC Help
Powered by ViewVC 1.1.22