/[MITgcm]/MITgcm/pkg/ctrl/ctrl_set_unpack_xy.F
ViewVC logotype

Contents of /MITgcm/pkg/ctrl/ctrl_set_unpack_xy.F

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


Revision 1.18 - (show annotations) (download)
Thu Apr 27 12:50:39 2006 UTC (18 years ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59, checkpoint58f_post, checkpoint58y_post, checkpoint58t_post, checkpoint58m_post, checkpoint58w_post, checkpoint58o_post, checkpoint58p_post, checkpoint58q_post, checkpoint58e_post, checkpoint58r_post, checkpoint58n_post, checkpoint59a, checkpoint59c, checkpoint59b, checkpoint58k_post, checkpoint58v_post, checkpoint58l_post, checkpoint58g_post, checkpoint58x_post, checkpoint58h_post, checkpoint58j_post, checkpoint58i_post, checkpoint58u_post, checkpoint58s_post
Changes since 1.17: +4 -2 lines
o supressing admtlm-related vector output for now
  (such ad admtlm_vector, admtlm_eigen)

1
2 #include "CTRL_CPPOPTIONS.h"
3
4 subroutine ctrl_set_unpack_xy(
5 & lxxadxx, cunit, ivartype, fname, masktype, weighttype,
6 & nwetglobal, mythid)
7
8 c ==================================================================
9 c SUBROUTINE ctrl_set_unpack_xy
10 c ==================================================================
11 c
12 c o Unpack the control vector such that the land points are filled
13 c in.
14 c
15 c changed: heimbach@mit.edu 17-Jun-2003
16 c merged Armin's changes to replace write of
17 c nr * globfld2d by 1 * globfld3d
18 c (ad hoc fix to speed up global I/O)
19 c
20 c ==================================================================
21
22 implicit none
23
24 c == global variables ==
25
26 #include "EEPARAMS.h"
27 #include "SIZE.h"
28 #include "PARAMS.h"
29 #include "GRID.h"
30
31 #include "ctrl.h"
32 #include "optim.h"
33
34 c == routine arguments ==
35
36 logical lxxadxx
37 integer cunit
38 integer ivartype
39 character*( 80) fname, fnameGlobal
40 character*( 9) masktype
41 character*( 80) weighttype
42 integer nwetglobal(nr)
43 integer mythid
44
45 c == local variables ==
46
47 integer bi,bj
48 integer ip,jp
49 integer i,j,k
50 integer ii
51 integer il
52 integer irec,nrec_nl
53 integer itlo,ithi
54 integer jtlo,jthi
55 integer jmin,jmax
56 integer imin,imax
57
58 integer cbuffindex
59
60 _RL globmsk ( snx,nsx,npx,sny,nsy,npy,nr )
61 _RL globfld3d( snx,nsx,npx,sny,nsy,npy,nr )
62 _RL globfld2d( snx,nsx,npx,sny,nsy,npy )
63 real*4 cbuff ( snx*nsx*npx*sny*nsy*npy )
64
65 character*(128) cfile
66 character*( 80) weightname
67
68 integer reclen,irectrue
69 integer cunit2, cunit3
70 character*(80) cfile2, cfile3
71 real*4 globfldtmp2( snx,nsx,npx,sny,nsy,npy )
72 real*4 globfldtmp3( snx,nsx,npx,sny,nsy,npy )
73
74 c == external ==
75
76 integer ilnblnk
77 external ilnblnk
78
79 c == end of interface ==
80
81 jtlo = 1
82 jthi = nsy
83 itlo = 1
84 ithi = nsx
85 jmin = 1
86 jmax = sny
87 imin = 1
88 imax = snx
89
90 nbuffGlobal = nbuffGlobal + 1
91
92 c Initialise temporary file
93 do k = 1,nr
94 do jp = 1,nPy
95 do bj = jtlo,jthi
96 do j = jmin,jmax
97 do ip = 1,nPx
98 do bi = itlo,ithi
99 do i = imin,imax
100 globfld3d (i,bi,ip,j,bj,jp,k) = 0. _d 0
101 globmsk (i,bi,ip,j,bj,jp,k) = 0. _d 0
102 globfldtmp2(i,bi,ip,j,bj,jp) = 0.
103 globfldtmp3(i,bi,ip,j,bj,jp) = 0.
104 enddo
105 enddo
106 enddo
107 enddo
108 enddo
109 enddo
110 enddo
111
112 c-- Only the master thread will do I/O.
113 _BEGIN_MASTER( mythid )
114
115 if ( doPackDiag ) then
116 write(cfile2(1:80),'(80a)') ' '
117 write(cfile3(1:80),'(80a)') ' '
118 if ( lxxadxx ) then
119 write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
120 & 'diag_unpack_nondim_ctrl_',
121 & ivartype, '_', optimcycle, '.bin'
122 write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
123 & 'diag_unpack_dimens_ctrl_',
124 & ivartype, '_', optimcycle, '.bin'
125 else
126 write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
127 & 'diag_unpack_nondim_grad_',
128 & ivartype, '_', optimcycle, '.bin'
129 write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
130 & 'diag_unpack_dimens_grad_',
131 & ivartype, '_', optimcycle, '.bin'
132 endif
133
134 reclen = FLOAT(snx*nsx*npx*sny*nsy*npy*4)
135 call mdsfindunit( cunit2, mythid )
136 open( cunit2, file=cfile2, status='unknown',
137 & access='direct', recl=reclen )
138 call mdsfindunit( cunit3, mythid )
139 open( cunit3, file=cfile3, status='unknown',
140 & access='direct', recl=reclen )
141 endif
142
143 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
144 il=ilnblnk( weighttype)
145 write(weightname(1:80),'(80a)') ' '
146 write(weightname(1:80),'(a)') weighttype(1:il)
147 call MDSREADFIELD_2D_GL(
148 & weightname, ctrlprec, 'RL',
149 & 1, globfld2d, 1, mythid)
150 #endif
151
152 call MDSREADFIELD_3D_GL(
153 & masktype, ctrlprec, 'RL',
154 & Nr, globmsk, 1, mythid)
155
156 nrec_nl=int(ncvarrecs(ivartype)/Nr)
157 do irec = 1, nrec_nl
158 do k = 1,Nr
159 irectrue = (irec-1)*nr + k
160 #ifndef ALLOW_ADMTLM
161 read(cunit) filencvarindex(ivartype)
162 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
163 & then
164 print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
165 & filencvarindex(ivartype), ncvarindex(ivartype)
166 STOP 'in S/R ctrl_unpack'
167 endif
168 read(cunit) filej
169 read(cunit) filei
170 #endif /* ndef ALLOW_ADMTLM */
171 cbuffindex = nwetglobal(1)
172 if ( cbuffindex .gt. 0 ) then
173 #ifndef ALLOW_ADMTLM
174 read(cunit) filencbuffindex
175 if (filencbuffindex .NE. cbuffindex) then
176 print *, 'WARNING: wrong cbuffindex ',
177 & filencbuffindex, cbuffindex
178 STOP 'in S/R ctrl_unpack'
179 endif
180 read(cunit) filek
181 if (filek .NE. 1) then
182 print *, 'WARNING: wrong k ',
183 & filek, 1
184 STOP 'in S/R ctrl_unpack'
185 endif
186 cph#endif /* ndef ALLOW_ADMTLM */
187 read(cunit) (cbuff(ii), ii=1,cbuffindex)
188 #endif /* ndef ALLOW_ADMTLM */
189 endif
190 c
191 cbuffindex = 0
192 do jp = 1,nPy
193 do bj = jtlo,jthi
194 do j = jmin,jmax
195 do ip = 1,nPx
196 do bi = itlo,ithi
197 do i = imin,imax
198 if ( globmsk(i,bi,ip,j,bj,jp,1) .ne. 0. ) then
199 cbuffindex = cbuffindex + 1
200 globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
201 cph(
202 globfldtmp2(i,bi,ip,j,bj,jp) = cbuff(cbuffindex)
203 cph)
204 #ifdef ALLOW_ADMTLM
205 nveccount = nveccount + 1
206 globfld3d(i,bi,ip,j,bj,jp,k) =
207 & phtmpadmtlm(nveccount)
208 cph(
209 globfldtmp2(i,bi,ip,j,bj,jp) =
210 & phtmpadmtlm(nveccount)
211 cph)
212 #endif
213 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
214 if ( lxxadxx ) then
215 globfld3d(i,bi,ip,j,bj,jp,k) =
216 & globfld3d(i,bi,ip,j,bj,jp,k)/
217 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
218 else
219 globfld3d(i,bi,ip,j,bj,jp,k) =
220 & globfld3d(i,bi,ip,j,bj,jp,k)*
221 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
222 endif
223 #endif
224 else
225 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
226 endif
227 cph(
228 globfldtmp3(i,bi,ip,j,bj,jp) =
229 & globfld3d(i,bi,ip,j,bj,jp,k)
230 cph)
231 enddo
232 enddo
233 enddo
234 enddo
235 enddo
236 enddo
237 cph(
238 if ( doPackDiag ) then
239 write(cunit2,rec=irectrue) globfldtmp2
240 write(cunit3,rec=irectrue) globfldtmp3
241 endif
242 cph)
243 enddo
244
245 call MDSWRITEFIELD_3D_GL( fname, ctrlprec, 'RL',
246 & NR, globfld3d,
247 & irec, optimcycle, mythid)
248
249 enddo
250
251 do irec = nrec_nl*Nr+1,ncvarrecs(ivartype)
252 #ifndef ALLOW_ADMTLM
253 read(cunit) filencvarindex(ivartype)
254 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
255 & then
256 print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
257 & filencvarindex(ivartype), ncvarindex(ivartype)
258 STOP 'in S/R ctrl_unpack'
259 endif
260 read(cunit) filej
261 read(cunit) filei
262 #endif /* ALLOW_ADMTLM */
263 do k = 1,1
264 irectrue = irec
265 cbuffindex = nwetglobal(k)
266 if ( cbuffindex .gt. 0 ) then
267 #ifndef ALLOW_ADMTLM
268 read(cunit) filencbuffindex
269 if (filencbuffindex .NE. cbuffindex) then
270 print *, 'WARNING: wrong cbuffindex ',
271 & filencbuffindex, cbuffindex
272 STOP 'in S/R ctrl_unpack'
273 endif
274 read(cunit) filek
275 if (filek .NE. k) then
276 print *, 'WARNING: wrong k ',
277 & filek, k
278 STOP 'in S/R ctrl_unpack'
279 endif
280 cph#endif /* ALLOW_ADMTLM */
281 read(cunit) (cbuff(ii), ii=1,cbuffindex)
282 #endif /* ALLOW_ADMTLM */
283 endif
284 c
285 cbuffindex = 0
286 do jp = 1,nPy
287 do bj = jtlo,jthi
288 do j = jmin,jmax
289 do ip = 1,nPx
290 do bi = itlo,ithi
291 do i = imin,imax
292 if ( globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
293 cbuffindex = cbuffindex + 1
294 globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
295 cph(
296 globfldtmp2(i,bi,ip,j,bj,jp) = cbuff(cbuffindex)
297 cph)
298 #ifdef ALLOW_ADMTLM
299 nveccount = nveccount + 1
300 globfld3d(i,bi,ip,j,bj,jp,k) =
301 & phtmpadmtlm(nveccount)
302 cph(
303 globfldtmp2(i,bi,ip,j,bj,jp) =
304 & phtmpadmtlm(nveccount)
305 cph)
306 #endif
307 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
308 if ( lxxadxx ) then
309 globfld3d(i,bi,ip,j,bj,jp,k) =
310 & globfld3d(i,bi,ip,j,bj,jp,k)/
311 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
312 else
313 globfld3d(i,bi,ip,j,bj,jp,k) =
314 & globfld3d(i,bi,ip,j,bj,jp,k)*
315 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
316 endif
317 #endif
318 else
319 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
320 endif
321 cph(
322 globfldtmp3(i,bi,ip,j,bj,jp) =
323 & globfld3d(i,bi,ip,j,bj,jp,k)
324 cph)
325 enddo
326 enddo
327 enddo
328 enddo
329 enddo
330 enddo
331 cph(
332 if ( doPackDiag ) then
333 write(cunit2,rec=irectrue) globfldtmp2
334 write(cunit3,rec=irectrue) globfldtmp3
335 endif
336 cph)
337 enddo
338
339 call MDSWRITEFIELD_2D_GL( fname, ctrlprec, 'RL',
340 & 1, globfld3d(1,1,1,1,1,1,1),
341 & irec, optimcycle, mythid)
342
343 enddo
344
345 if ( doPackDiag ) then
346 close ( cunit2 )
347 close ( cunit3 )
348 endif
349
350 _END_MASTER( mythid )
351
352 return
353 end
354

  ViewVC Help
Powered by ViewVC 1.1.22