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

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

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


Revision 1.1 - (show annotations) (download)
Thu Nov 6 22:10:07 2003 UTC (20 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint53f_post, checkpoint54a_pre, checkpoint55c_post, checkpoint53b_pre, checkpoint52l_pre, checkpoint52e_pre, hrcube4, hrcube5, checkpoint52j_post, checkpoint52e_post, checkpoint52d_pre, checkpoint53c_post, checkpoint53d_post, checkpoint55d_pre, checkpoint52j_pre, checkpoint54a_post, branch-netcdf, checkpoint52b_pre, checkpoint52n_post, checkpoint54b_post, checkpoint54d_post, checkpoint54e_post, checkpoint55b_post, checkpoint52m_post, checkpoint55, checkpoint53a_post, checkpoint55a_post, checkpoint52l_post, checkpoint52k_post, checkpoint54, checkpoint53b_post, checkpoint53, checkpoint52, checkpoint52d_post, checkpoint52a_post, checkpoint52b_post, checkpoint53g_post, checkpoint52f_post, checkpoint52c_post, ecco_c52_e35, checkpoint54f_post, checkpoint52a_pre, checkpoint53d_pre, checkpoint54c_post, checkpoint52i_post, checkpoint52i_pre, checkpoint51u_post, checkpoint52h_pre, checkpoint52f_pre, hrcube_1, 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 C $Header: /u/gcmpack/MITgcm/pkg/cost/Attic/cost_readsstfields.F,v 1.1.2.2 2003/06/19 15:21:16 heimbach Exp $
2
3 #include "COST_CPPOPTIONS.h"
4
5
6 subroutine cost_ReadSSTFields(
7 I irec,
8 I mythid
9 & )
10
11 c ==================================================================
12 c SUBROUTINE cost_ReadSSTFields
13 c ==================================================================
14 c
15 c o Read a given record of the SST 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_ReadSSTFields
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 c == local variables ==
46
47 integer bi,bj
48 integer i,j,k
49 integer itlo,ithi
50 integer jtlo,jthi
51 integer jmin,jmax
52 integer imin,imax
53 integer nobs
54 integer sstrec
55 integer beginsst
56 integer beginrun
57
58 _RL spval
59 _RL vartile
60
61 c == end of interface ==
62
63 parameter (spval = -1.8 )
64 ce --> there is certainly a better place for this.
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 beginsst = sststartdate(1)/10000
76 beginrun = modelstartdate(1)/10000
77
78 if ( beginsst .eq. beginrun ) then
79 sstrec = mod(modelstartdate(1)/100,100) -
80 & mod(sststartdate(1)/100,100) + irec
81 else
82 sstrec = ( beginrun - beginsst - 1)*nmonthyear +
83 & (nmonthyear - mod(sststartdate(1)/100,100) +
84 & 1) + mod(modelstartdate(1)/100,100) - 1 + irec
85 endif
86
87 if ( sstrec.gt.0 .and. sstdatfile .ne. ' ' ) then
88 call mdsreadfield( sstdatfile, cost_iprec, cost_yftype, 1,
89 & sstdat, sstrec, mythid )
90 else
91 do bj = jtlo,jthi
92 do bi = itlo,ithi
93 do j = jmin,jmax
94 do i = imin,imax
95 sstdat(i,j,bi,bj)=spval
96 enddo
97 enddo
98 enddo
99 enddo
100 endif
101
102 nobs = 0
103 do bj = jtlo,jthi
104 do bi = itlo,ithi
105 k = 1
106 do j = jmin,jmax
107 do i = imin,imax
108
109 if (_hFacC(i,j,k,bi,bj) .eq. 0.) then
110 sstmask(i,j,bi,bj) = 0. _d 0
111 else
112 sstmask(i,j,bi,bj) = 1. _d 0
113 endif
114 if (sstdat(i,j,bi,bj) .le. spval) then
115 sstmask(i,j,bi,bj) = 0. _d 0
116 endif
117 if (sstdat(i,j,bi,bj) .eq. 0. _d 0 ) then
118 sstmask(i,j,bi,bj) = 0. _d 0
119 endif
120
121 sstmask(i,j,bi,bj) = sstmask(i,j,bi,bj)*frame(i,j)
122 sstdat(i,j,bi,bj) = sstdat(i,j,bi,bj)*sstmask(i,j,bi,bj)
123 nobs = nobs + int(sstmask(i,j,bi,bj))
124
125 enddo
126 enddo
127 enddo
128 enddo
129
130 c-- Calculate the field variance for present subdomain.
131 c-- One could of course do a global sum here.
132 vartile = 0. _d 0
133 do bj = jtlo,jthi
134 do bi = itlo,ithi
135 do j = jmin,jmax
136 do i = imin,imax
137 vartile = vartile + sstdat(i,j,bi,bj)*sstdat(i,j,bi,bj)
138 enddo
139 enddo
140 enddo
141 enddo
142
143 if (nobs .gt. 0) then
144 vartile = vartile/float(nobs)
145 else
146 vartile = spval
147 endif
148
149 return
150 end
151

  ViewVC Help
Powered by ViewVC 1.1.22