/[MITgcm]/MITgcm/optim/optim_readdata.F
ViewVC logotype

Annotation of /MITgcm/optim/optim_readdata.F

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


Revision 1.8 - (hide annotations) (download)
Tue May 10 07:53:24 2011 UTC (12 years, 11 months ago) by mlosch
Branch: MAIN
CVS Tags: checkpoint62z, checkpoint62y, checkpoint62x, checkpoint63
Changes since 1.7: +12 -0 lines
adjust after introducing new control variable xx_shifwflx

1 heimbach 1.2
2     subroutine optim_readdata(
3     I nn,
4     I dfile,
5     I lheaderonly,
6     O ff,
7     O vv
8     & )
9    
10     c ==================================================================
11     c SUBROUTINE optim_readdata
12     c ==================================================================
13     c
14     c o Read the data written by the MITgcmUV state estimation setup and
15     c join them to one vector that is subsequently used by the minimi-
16     c zation algorithm "lsopt". Depending on the specified file name
17     c either the control vector or the gradient vector can be read.
18     c
19     c *dfile* should be the radix of the file: ecco_ctrl or ecco_cost
20     c
21     c started: Christian Eckert eckert@mit.edu 12-Apr-2000
22     c
23     c changed: Patrick Heimbach heimbach@mit.edu 19-Jun-2000
24     c - finished, revised and debugged
25     c
26     c ==================================================================
27     c SUBROUTINE optim_readdata
28     c ==================================================================
29    
30     implicit none
31    
32     c == global variables ==
33    
34     #include "EEPARAMS.h"
35     #include "SIZE.h"
36     cgg Include ECCO_CPPOPTIONS because the ecco_ctrl,cost files
37     cgg have headers with options for OBCS masks.
38     #include "ECCO_CPPOPTIONS.h"
39    
40     #include "ctrl.h"
41     #include "optim.h"
42     #include "minimization.h"
43    
44     c == routine arguments ==
45    
46     integer nn
47     _RL ff
48    
49     #if defined (DYNAMIC)
50     _RL vv(nn)
51     #elif defined (USE_POINTER) || (MAX_INDEPEND == 0)
52     _RL vv
53     pointer (pvv,vv(1))
54     #else
55     integer nmax
56     parameter( nmax = MAX_INDEPEND )
57     _RL vv(nmax)
58     #endif
59    
60     character*(9) dfile
61     logical lheaderonly
62    
63     c == local variables ==
64    
65     integer bi,bj
66     integer biG,bjG
67     integer i,j
68     integer ii,k
69     integer icvar
70     integer icvrec
71     integer icvcomp
72     integer icvoffset
73     integer nopt
74     integer funit
75    
76     integer cbuffindex
77 heimbach 1.5 real*4 cbuff( sNx*nSx*nPx*sNy*nSy*nPy )
78 heimbach 1.2
79     character*(128) fname
80    
81 heimbach 1.6 c integer filei
82     c integer filej
83     c integer filek
84 dfer 1.7 c integer fileiG
85     c integer filejG
86 heimbach 1.6 c integer filensx
87     c integer filensy
88 heimbach 1.2 integer filenopt
89     _RL fileff
90    
91     cgg(
92     _RL gg
93     integer igg
94     integer iobcs
95     cgg)
96    
97     c == end of interface ==
98    
99 heimbach 1.6 print *, 'pathei-lsopt in optim_readdata'
100    
101 heimbach 1.2 c-- The reference i/o unit.
102     funit = 20
103    
104     c-- Next optimization cycle.
105     nopt = optimcycle
106    
107     if ( dfile .eq. ctrlname ) then
108     print*
109     print*,' OPTIM_READDATA: Reading control vector'
110     print*,' for optimization cycle: ',nopt
111     print*
112     else if ( dfile .eq. costname ) then
113     print*
114     print*,' OPTIM_READDATA: Reading cost function and'
115     print*,' gradient of cost function'
116     print*,' for optimization cycle: ',nopt
117     print*
118     else
119     print*
120     print*,' OPTIM_READDATA: subroutine called by a false *dfile*'
121     print*,' argument. *dfile* = ',dfile
122     print*
123     stop ' ... stopped in OPTIM_READDATA.'
124     endif
125    
126     c-- Read the data.
127    
128     bjG = 1 + (myygloballo - 1)/sny
129     biG = 1 + (myxgloballo - 1)/snx
130    
131     c-- Generate file name and open the file.
132     write(fname(1:128),'(4a,i4.4)')
133 dfer 1.7 & dfile,'_',yctrlid(1:10),'.opt', nopt
134 heimbach 1.2 open( funit, file = fname,
135     & status = 'old',
136     & form = 'unformatted',
137     & access = 'sequential' )
138     print*, 'opened file ', fname
139    
140     c-- Read the header.
141     read( funit ) nvartype
142     read( funit ) nvarlength
143 dfer 1.7 read( funit ) yctrlid
144 heimbach 1.2 read( funit ) filenopt
145     read( funit ) fileff
146     read( funit ) fileiG
147     read( funit ) filejG
148     read( funit ) filensx
149     read( funit ) filensy
150    
151 heimbach 1.3 read( funit ) (nWetcGlobal(k), k=1,nr)
152     read( funit ) (nWetsGlobal(k), k=1,nr)
153     read( funit ) (nWetwGlobal(k), k=1,nr)
154 heimbach 1.4 #ifdef ALLOW_CTRL_WETV
155 heimbach 1.3 read( funit ) (nWetvGlobal(k), k=1,nr)
156 heimbach 1.4 #endif
157 mlosch 1.8 #ifdef ALLOW_SHIFWFLX_CONTROL
158     read(funit) (nWetiGlobal(k), k=1,nr)
159     c read(funit) nWetiGlobal(1)
160     #endif
161 heimbach 1.2
162     cgg( Add OBCS Mask information into the header section for optimization.
163     #ifdef ALLOW_OBCSN_CONTROL
164 heimbach 1.3 read( funit ) ((nWetobcsnGlo(k,iobcs), k=1,nr),iobcs= 1,nobcs)
165 heimbach 1.2 #endif
166     #ifdef ALLOW_OBCSS_CONTROL
167 heimbach 1.3 read( funit ) ((nWetobcssGlo(k,iobcs), k=1,nr),iobcs= 1,nobcs)
168 heimbach 1.2 #endif
169     #ifdef ALLOW_OBCSW_CONTROL
170 heimbach 1.3 read( funit ) ((nWetobcswGlo(k,iobcs), k=1,nr),iobcs= 1,nobcs)
171 heimbach 1.2 #endif
172     #ifdef ALLOW_OBCSE_CONTROL
173 heimbach 1.3 read( funit ) ((nWetobcseGlo(k,iobcs), k=1,nr),iobcs= 1,nobcs)
174 heimbach 1.2 #endif
175     cgg)
176     read( funit ) (ncvarindex(i), i=1,maxcvars)
177     read( funit ) (ncvarrecs(i), i=1,maxcvars)
178     read( funit ) (ncvarxmax(i), i=1,maxcvars)
179     read( funit ) (ncvarymax(i), i=1,maxcvars)
180     read( funit ) (ncvarnrmax(i), i=1,maxcvars)
181     read( funit ) (ncvargrd(i), i=1,maxcvars)
182     read( funit )
183    
184     cph(
185     cph if (lheaderonly) then
186     print *, 'pathei: nvartype ', nvartype
187     print *, 'pathei: nvarlength ', nvarlength
188 dfer 1.7 print *, 'pathei: yctrlid ', yctrlid
189 heimbach 1.2 print *, 'pathei: filenopt ', filenopt
190     print *, 'pathei: fileff ', fileff
191     print *, 'pathei: fileiG ', fileiG
192     print *, 'pathei: filejG ', filejG
193     print *, 'pathei: filensx ', filensx
194     print *, 'pathei: filensy ', filensy
195    
196 heimbach 1.3 print *, 'pathei: nWetcGlobal ',
197     & (nWetcGlobal(k), k=1,nr)
198     print *, 'pathei: nWetsGlobal ',
199     & (nWetsGlobal(k), k=1,nr)
200     print *, 'pathei: nWetwGlobal ',
201     & (nWetwGlobal(k), k=1,nr)
202     print *, 'pathei: nWetvGlobal ',
203     & (nWetvGlobal(k), k=1,nr)
204 mlosch 1.8 #ifdef ALLOW_SHIFWFLX_CONTROL
205     print *, 'pathei: nWetiGlobal ',
206     & (nWetiGlobal(k), k=1,nr)
207     #endif
208 heimbach 1.2 print *, 'pathei: ncvarindex ',
209     & (ncvarindex(i), i=1,maxcvars)
210     print *, 'pathei: ncvarrecs ',
211     & (ncvarrecs(i), i=1,maxcvars)
212     print *, 'pathei: ncvarxmax ',
213     & (ncvarxmax(i), i=1,maxcvars)
214     print *, 'pathei: ncvarymax ',
215     & (ncvarymax(i), i=1,maxcvars)
216     print *, 'pathei: ncvarnrmax ',
217     & (ncvarnrmax(i), i=1,maxcvars)
218     print *, 'pathei: ncvargrd ',
219     & (ncvargrd(i), i=1,maxcvars)
220     cph end if
221     cph)
222     c-- Check the header information for consistency.
223    
224     cph if ( filenopt .ne. nopt ) then
225     cph print*
226     cph print*,' READ_HEADER: Input data belong to the wrong'
227     cph print*,' optimization cycle.'
228     cph print*,' optimization cycle = ',nopt
229     cph print*,' input optim cycle = ',filenopt
230     cph print*
231     cph stop ' ... stopped in READ_HEADER.'
232     cph endif
233    
234     if ( (fileiG .ne. biG) .or. (filejG .ne. bjG) ) then
235     print*
236     print*,' READ_HEADER: Tile indices of loop and data '
237     print*,' do not match.'
238     print*,' loop x/y component = ',
239     & biG,bjG
240     print*,' data x/y component = ',
241     & fileiG,filejG
242     print*
243     stop ' ... stopped in READ_HEADER.'
244     endif
245    
246     if ( (filensx .ne. nsx) .or. (filensy .ne. nsy) ) then
247     print*
248     print*,' READ_HEADER: Numbers of tiles do not match.'
249     print*,' parameter x/y no. of tiles = ',
250     & bi,bj
251     print*,' data x/y no. of tiles = ',
252     & filensx,filensy
253     print*
254     stop ' ... stopped in READ_HEADER.'
255     endif
256    
257     ce Add some more checks. ...
258    
259     if (.NOT. lheaderonly) then
260     c-- Read the data.
261     icvoffset = 0
262     do icvar = 1,maxcvars
263     if ( ncvarindex(icvar) .ne. -1 ) then
264     do icvrec = 1,ncvarrecs(icvar)
265     do bj = 1,nsy
266     do bi = 1,nsx
267     read( funit ) ncvarindex(icvar)
268     read( funit ) filej
269     read( funit ) filei
270     do k = 1,ncvarnrmax(icvar)
271     cbuffindex = 0
272     if (ncvargrd(icvar) .eq. 'c') then
273 heimbach 1.3 cbuffindex = nWetcGlobal(k)
274 heimbach 1.2 else if (ncvargrd(icvar) .eq. 's') then
275 heimbach 1.3 cbuffindex = nWetsGlobal(k)
276 heimbach 1.2 else if (ncvargrd(icvar) .eq. 'w') then
277 heimbach 1.3 cbuffindex = nWetwGlobal(k)
278     else if (ncvargrd(icvar) .eq. 'v') then
279     cbuffindex = nWetvGlobal(k)
280 mlosch 1.8 #ifdef ALLOW_SHIFWFLX_CONTROL
281     else if (ncvargrd(icvar) .eq. 'i') then
282     cbuffindex = nWetiGlobal(k)
283     #endif
284 heimbach 1.2 cgg( O.B. points have the grid mask "m".
285     else if (ncvargrd(icvar) .eq. 'm') then
286     cgg From "icvrec", calculate what iobcs must be.
287     gg = (icvrec-1)/nobcs
288     igg = int(gg)
289     iobcs= icvrec - igg*nobcs
290     #ifdef ALLOW_OBCSN_CONTROL
291     if (icvar .eq. 11) then
292 heimbach 1.3 cbuffindex = nWetobcsnGlo(k,iobcs)
293 heimbach 1.2 endif
294     #endif
295     #ifdef ALLOW_OBCSS_CONTROL
296     if (icvar .eq. 12) then
297 heimbach 1.3 cbuffindex = nWetobcssGlo(k,iobcs)
298 heimbach 1.2 endif
299     #endif
300     #ifdef ALLOW_OBCSW_CONTROL
301     if (icvar .eq. 13) then
302 heimbach 1.3 cbuffindex = nWetobcswGlo(k,iobcs)
303 heimbach 1.2 endif
304     #endif
305     #ifdef ALLOW_OBCSE_CONTROL
306     if (icvar .eq. 14) then
307 heimbach 1.3 cbuffindex = nWetobcseGlo(k,iobcs)
308 heimbach 1.2 endif
309     #endif
310     cgg)
311     endif
312     if (cbuffindex .gt. 0) then
313     read( funit ) cbuffindex
314     read( funit ) filek
315     read( funit ) (cbuff(ii), ii=1,cbuffindex)
316     do icvcomp = 1,cbuffindex
317     vv(icvoffset+icvcomp) = cbuff(icvcomp)
318     cgg( Right now, the changes to the open boundary velocities are not balanced.
319     cgg( The model will crash due to physical reasons.
320     cgg( However, we can optimize with respect to just O.B. T and S if the
321     cgg( next two lines are uncommented.
322     cgg if (iobcs .eq. 3) vv(icvoffset+icvcomp)=0.
323     cgg if (iobcs .eq. 4) vv(icvoffset+icvcomp)=0.
324     enddo
325     icvoffset = icvoffset + cbuffindex
326     endif
327     enddo
328     enddo
329     enddo
330     enddo
331     endif
332     enddo
333    
334     else
335    
336     c-- Assign the number of control variables.
337     nn = nvarlength
338    
339     endif
340    
341     close( funit )
342    
343     c-- Assign the cost function value in case we read the cost file.
344    
345     if ( dfile .eq. ctrlname ) then
346     ff = 0. d 0
347     else if ( dfile .eq. costname ) then
348     ff = fileff
349     endif
350    
351     return
352     end

  ViewVC Help
Powered by ViewVC 1.1.22