/[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.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_readers.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_ReadERS(
7     I irec,
8     I mythid
9     & )
10    
11     c ==================================================================
12     c SUBROUTINE cost_ReadERS
13     c ==================================================================
14     c
15     c o Read a given record of the ERS 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 changed: Armin Koehl akoehl@ucsd.edu 17-Mar-2003
25     c
26     c ==================================================================
27     c SUBROUTINE cost_ReadERS
28     c ==================================================================
29    
30     implicit none
31    
32     c == global variables ==
33    
34     #include "EEPARAMS.h"
35     #include "SIZE.h"
36     #include "PARAMS.h"
37     #include "GRID.h"
38    
39     #include "cal.h"
40     #include "ecco_cost.h"
41    
42     c == routine arguments ==
43    
44     integer irec
45     integer mythid
46    
47     #ifdef ALLOW_SSH_ERSANOM_COST_CONTRIBUTION
48     c == local variables ==
49    
50     integer bi,bj
51     integer i,j,k
52     integer itlo,ithi
53     integer jtlo,jthi
54     integer jmin,jmax
55     integer imin,imax
56     integer sshrec
57     integer nobs
58     integer difftime(4)
59     integer middate(4)
60     integer noffset
61     _RL diffsecs
62     _RL spval
63     _RL factor
64     _RL vartile
65    
66     c == end of interface ==
67    
68     jtlo = mybylo(mythid)
69     jthi = mybyhi(mythid)
70     itlo = mybxlo(mythid)
71     ithi = mybxhi(mythid)
72     jmin = 1
73     jmax = sny
74     imin = 1
75     imax = snx
76    
77     factor = 0.01
78     spval = -9990.
79    
80     middate(1) = modelstartdate(1)
81     middate(2) = 120000
82     middate(3) = modelstartdate(3)
83     middate(4) = modelstartdate(4)
84    
85     call cal_TimePassed( ersstartdate, middate, difftime, mythid )
86     call cal_ToSeconds( difftime, diffsecs, mythid )
87    
88     noffset = int(diffsecs/ersperiod)
89     sshrec = noffset + irec
90     nobs = 0
91    
92     if ( sshrec .gt. 0 .and. ersfile .ne. ' ' ) then
93     call mdsreadfield( ersfile, cost_iprec, cost_yftype, 1, ersobs,
94     & sshrec, mythid )
95     else
96     do bj = jtlo,jthi
97     do bi = itlo,ithi
98     do j = jmin,jmax
99     do i = imin,imax
100     ersobs(i,j,bi,bj)=spval
101     enddo
102     enddo
103     enddo
104     enddo
105     endif
106    
107     do bj = jtlo,jthi
108     do bi = itlo,ithi
109     k = 1
110     do j = jmin,jmax
111     do i = imin,imax
112     if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
113     ersmask(i,j,bi,bj) = 0. _d 0
114     else
115     ersmask(i,j,bi,bj) = 1. _d 0
116     endif
117     if (ersobs(i,j,bi,bj) .le. spval) then
118     ersmask(i,j,bi,bj) = 0. _d 0
119     endif
120     if (abs(ersobs(i,j,bi,bj)) .lt. 1.d-8 ) then
121     ersmask(i,j,bi,bj) = 0. _d 0
122     endif
123    
124     cph(
125     cph print *, 'WARNING: SPECIFIC SETUP FOR ECCO'
126     cph below statement could be replaced by following
127     cph to make it independnet of Nr:
128     cph
129     cph if ( rC(K) .GT. -1000. ) then
130     cph)
131     c set tpmask=0 in areas shallower than 1000m
132     if (_hFacC(i,j,13,bi,bj) .eq. 0.) then
133     ersmask(i,j,bi,bj) = 0. _d 0
134     endif
135    
136     ersmask(i,j,bi,bj) = ersmask(i,j,bi,bj)*frame(i,j)
137     ersobs(i,j,bi,bj) = ersobs(i,j,bi,bj)*
138     * ersmask(i,j,bi,bj)*
139     & factor
140     nobs = nobs + int(ersmask(i,j,bi,bj))
141     enddo
142     enddo
143     enddo
144     enddo
145    
146     c-- Calculate the field variance for present subdomain.
147     c-- one could of course do a global sum here.
148     vartile = 0. _d 0
149     do bj = jtlo,jthi
150     do bi = itlo,ithi
151     do j = jmin,jmax
152     do i = imin,imax
153     vartile = vartile + ersobs(i,j,bi,bj)*
154     & ersobs(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     #endif
167    
168     return
169     end
170    

  ViewVC Help
Powered by ViewVC 1.1.22