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

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

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


Revision 1.1 - (hide annotations) (download)
Thu Nov 6 22:10:07 2003 UTC (20 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint52l_pre, checkpoint52e_pre, hrcube4, checkpoint52n_post, checkpoint52j_post, checkpoint53d_post, checkpoint54a_pre, checkpoint55c_post, checkpoint54e_post, checkpoint52e_post, checkpoint53c_post, checkpoint55d_pre, checkpoint52j_pre, checkpoint54a_post, branch-netcdf, checkpoint52d_pre, checkpoint52l_post, checkpoint52k_post, checkpoint52b_pre, checkpoint54b_post, checkpoint53b_pre, checkpoint55b_post, checkpoint54d_post, checkpoint53f_post, hrcube_1, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint54, checkpoint54f_post, checkpoint53b_post, checkpoint53, checkpoint52, checkpoint52d_post, checkpoint52a_post, checkpoint52b_post, checkpoint53g_post, checkpoint52f_post, checkpoint52c_post, ecco_c52_e35, hrcube5, checkpoint52a_pre, checkpoint52i_post, checkpoint55a_post, checkpoint53d_pre, checkpoint54c_post, checkpoint52i_pre, checkpoint51u_post, checkpoint52h_pre, checkpoint52f_pre, hrcube_2, hrcube_3
Branch point for: netcdf-sm0
o merging from ecco-branch
o pkg/ecco now containes ecco-specific part of cost function
o top level routines the_main_loop, forward_step
  supersede those in model/src/
  previous input data.cost now in data.ecco
  (new namelist ecco_cost_nml)

1 heimbach 1.1 C $Header: /u/gcmpack/MITgcm/pkg/cost/Attic/cost_readtopex.F,v 1.1.2.3 2003/06/19 15:21:16 heimbach Exp $
2    
3     #include "COST_CPPOPTIONS.h"
4    
5    
6     subroutine cost_ReadTopex(
7     I irec,
8     I mythid
9     & )
10    
11     c ==================================================================
12     c SUBROUTINE cost_ReadTopex
13     c ==================================================================
14     c
15     c o Read a given record of the TOPEX SSH 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_ReadTopex
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     #ifdef ALLOW_SSH_TPANOM_COST_CONTRIBUTION
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 sshrec
55     integer nobs
56     integer difftime(4)
57     integer middate(4)
58     integer noffset
59     _RL diffsecs
60     _RL spval
61     _RL factor
62     _RL vartile
63    
64     c == end of interface ==
65    
66     jtlo = mybylo(mythid)
67     jthi = mybyhi(mythid)
68     itlo = mybxlo(mythid)
69     ithi = mybxhi(mythid)
70     jmin = 1
71     jmax = sny
72     imin = 1
73     imax = snx
74    
75     factor = 0.01
76     spval = -9990.
77    
78     middate(1) = modelstartdate(1)
79     middate(2) = 120000
80     middate(3) = modelstartdate(3)
81     middate(4) = modelstartdate(4)
82    
83     call cal_TimePassed( topexstartdate, middate, difftime, mythid )
84     call cal_ToSeconds( difftime, diffsecs, mythid )
85    
86     noffset = int(diffsecs/topexperiod)
87     sshrec = noffset + irec
88     nobs = 0
89    
90     if ( sshrec.gt.0 .and. topexfile .ne. ' ' ) then
91     call mdsreadfield( topexfile, cost_iprec, cost_yftype, 1, tpobs,
92     & sshrec, mythid )
93     else
94     do bj = jtlo,jthi
95     do bi = itlo,ithi
96     do j = jmin,jmax
97     do i = imin,imax
98     tpobs(i,j,bi,bj)=spval
99     enddo
100     enddo
101     enddo
102     enddo
103     endif
104    
105     do bj = jtlo,jthi
106     do bi = itlo,ithi
107     k = 1
108     do j = jmin,jmax
109     do i = imin,imax
110     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
111     tpmask(i,j,bi,bj) = 0. _d 0
112     else
113     tpmask(i,j,bi,bj) = 1. _d 0
114     endif
115     if (tpobs(i,j,bi,bj) .le. spval) then
116     tpmask(i,j,bi,bj) = 0. _d 0
117     endif
118     if (abs(tpobs(i,j,bi,bj)) .lt. 1.d-8 ) then
119     tpmask(i,j,bi,bj) = 0. _d 0
120     endif
121    
122     cph(
123     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
124     cph below statement could be replaced by following
125     cph to make it independnet of Nr:
126     cph
127     cph if ( rC(K) .GT. -1000. ) then
128     cph)
129     c set tpmask=0 in areas shallower than 1000m
130     if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
131     tpmask(i,j,bi,bj) = 0. _d 0
132     endif
133    
134     tpmask(i,j,bi,bj) = tpmask(i,j,bi,bj)*frame(i,j)
135     tpobs(i,j,bi,bj) = tpobs(i,j,bi,bj)*
136     & tpmask(i,j,bi,bj)*
137     & factor
138     nobs = nobs + int(tpmask(i,j,bi,bj))
139     enddo
140     enddo
141     enddo
142     enddo
143    
144     c-- Calculate the field variance for present subdomain.
145     c-- One could of course do a global sum here.
146     vartile = 0. _d 0
147     do bj = jtlo,jthi
148     do bi = itlo,ithi
149     do j = jmin,jmax
150     do i = imin,imax
151     vartile = vartile + tpobs(i,j,bi,bj)*
152     & tpobs(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     #endif /* ALLOW_SSH_TPANOM_COST_CONTRIBUTION */
165    
166     return
167     end
168    

  ViewVC Help
Powered by ViewVC 1.1.22