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

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

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


Revision 1.9 - (hide annotations) (download)
Wed Mar 24 01:34:38 2010 UTC (14 years, 1 month ago) by jmc
Branch: MAIN
CVS Tags: checkpoint63h, checkpoint63i, checkpoint63j, checkpoint63d, checkpoint63e, checkpoint63f, checkpoint63g, checkpoint63a, checkpoint63b, checkpoint63c, checkpoint63, checkpoint62g, checkpoint62f, checkpoint62e, checkpoint62k, checkpoint62j, checkpoint62i, checkpoint62h, checkpoint62o, checkpoint62n, checkpoint62m, checkpoint62l, checkpoint62s, checkpoint62r, checkpoint62q, checkpoint62p, checkpoint62w, checkpoint62v, checkpoint62u, checkpoint62t, checkpoint62z, checkpoint62y, checkpoint62x
Changes since 1.8: +3 -4 lines
add missing "_d 0" ; affect lab_sea AD test (probably many more missing
 in pkg/ecco, but they do not affect our AD test).

1 jmc 1.9 C $Header: /u/gcmpack/MITgcm/pkg/ecco/cost_readers.F,v 1.8 2009/06/17 15:14:00 heimbach Exp $
2 jmc 1.7 C $Name: $
3 heimbach 1.1
4     #include "COST_CPPOPTIONS.h"
5    
6    
7 heimbach 1.4 subroutine cost_readers( irec, mythid )
8 heimbach 1.1
9     c ==================================================================
10 heimbach 1.4 c SUBROUTINE cost_readers
11 heimbach 1.1 c ==================================================================
12     c
13     c o Read a given record of the ERS 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 heimbach 1.4 c SUBROUTINE cost_readers
24 heimbach 1.1 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_ERSANOM_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 heimbach 1.2 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 jmc 1.7
73 heimbach 1.2 integer ilnblnk
74     external ilnblnk
75    
76 heimbach 1.1 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 jmc 1.9 factor = 0.01 _d 0
88     spval = -9990. _d 0
89 heimbach 1.1
90 heimbach 1.2 cnew(
91 gforget 1.6 daytime = FLOAT(secondsperday*(irec-1)) + modelstart
92     dayiter = hoursperday*(irec-1)+modeliter0
93 heimbach 1.2 call cal_getdate( dayiter, daytime, daydate, mythid )
94     call cal_convdate( daydate,yday,md,dd,sd,ld,wd,mythid )
95     ymod = ersstartdate(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 heimbach 1.1 middate(3) = modelstartdate(3)
104     middate(4) = modelstartdate(4)
105    
106 heimbach 1.2 call cal_TimePassed( middate, daydate, difftime, mythid )
107 heimbach 1.1 call cal_ToSeconds( difftime, diffsecs, mythid )
108 heimbach 1.2 sshrec = int(diffsecs/ersperiod) + 1
109 heimbach 1.1
110 heimbach 1.2 il=ilnblnk(ersfile)
111     write(fnametmp(1:80),'(2a,i4)')
112     & ersfile(1:il), '_', yday
113     inquire( file=fnametmp, exist=exst )
114     if (.NOT. exst) then
115     write(fnametmp(1:80),'(a)') ersfile(1:il)
116     sshrec = irec
117 heimbach 1.1 endif
118 jmc 1.7
119 heimbach 1.2 cnew)
120    
121    
122 jmc 1.7 call mdsreadfield( fnametmp, cost_iprec, cost_yftype, 1, ersobs,
123 heimbach 1.2 & sshrec, mythid )
124    
125    
126 heimbach 1.1 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     ersmask(i,j,bi,bj) = 0. _d 0
133     else
134     ersmask(i,j,bi,bj) = 1. _d 0
135     endif
136     if (ersobs(i,j,bi,bj) .le. spval) then
137     ersmask(i,j,bi,bj) = 0. _d 0
138     endif
139     if (abs(ersobs(i,j,bi,bj)) .lt. 1.d-8 ) then
140     ersmask(i,j,bi,bj) = 0. _d 0
141     endif
142    
143     cph(
144 heimbach 1.8 if ( R_low(i,j,bi,bj) .GT. -200. ) then
145 heimbach 1.1 ersmask(i,j,bi,bj) = 0. _d 0
146     endif
147 heimbach 1.8 cph)
148 heimbach 1.1
149     ersmask(i,j,bi,bj) = ersmask(i,j,bi,bj)*frame(i,j)
150 heimbach 1.5 ersobs(i,j,bi,bj) = ersmask(i,j,bi,bj)*factor*
151 jmc 1.7 & ( ersobs(i,j,bi,bj) -
152 heimbach 1.5 & ( ersintercept + ersslope*irec*hoursperday ) )
153 heimbach 1.1 enddo
154     enddo
155     enddo
156     enddo
157    
158     #endif
159    
160     return
161     end

  ViewVC Help
Powered by ViewVC 1.1.22