/[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.13 - (show annotations) (download)
Wed Jan 12 23:39:39 2005 UTC (19 years, 4 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57d_post, checkpoint57f_post, checkpoint57c_post, checkpoint57c_pre, checkpoint57e_post, eckpoint57e_pre, checkpoint57f_pre
Changes since 1.12: +2 -2 lines
o introduce z-scaling of
  * gradient (doZscalePack) and
  * control (doZscaleUnpack)

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*( 5) 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 print *, 'ph-pack nrec_nl = ', irec, nrec_nl, ivartype,
159 & ncvarrecs(ivartype)
160 do k = 1,Nr
161 irectrue = (irec-1)*nr + k
162 read(cunit) filencvarindex(ivartype)
163 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
164 & then
165 print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
166 & filencvarindex(ivartype), ncvarindex(ivartype)
167 STOP 'in S/R ctrl_unpack'
168 endif
169 read(cunit) filej
170 read(cunit) filei
171 cbuffindex = nwetglobal(1)
172 if ( cbuffindex .gt. 0 ) then
173 read(cunit) filencbuffindex
174 if (filencbuffindex .NE. cbuffindex) then
175 print *, 'WARNING: wrong cbuffindex ',
176 & filencbuffindex, cbuffindex
177 STOP 'in S/R ctrl_unpack'
178 endif
179 read(cunit) filek
180 if (filek .NE. 1) then
181 print *, 'WARNING: wrong k ',
182 & filek, 1
183 STOP 'in S/R ctrl_unpack'
184 endif
185 read(cunit) (cbuff(ii), ii=1,cbuffindex)
186 endif
187 cbuffindex = 0
188 do jp = 1,nPy
189 do bj = jtlo,jthi
190 do j = jmin,jmax
191 do ip = 1,nPx
192 do bi = itlo,ithi
193 do i = imin,imax
194 if ( globmsk(i,bi,ip,j,bj,jp,1) .ne. 0. ) then
195 cbuffindex = cbuffindex + 1
196 globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
197 cph(
198 globfldtmp2(i,bi,ip,j,bj,jp) = cbuff(cbuffindex)
199 cph)
200 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
201 if ( lxxadxx ) then
202 globfld3d(i,bi,ip,j,bj,jp,k) =
203 & globfld3d(i,bi,ip,j,bj,jp,k)/
204 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
205 else
206 globfld3d(i,bi,ip,j,bj,jp,k) =
207 & globfld3d(i,bi,ip,j,bj,jp,k)*
208 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
209 endif
210 #endif
211 else
212 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
213 endif
214 cph(
215 globfldtmp3(i,bi,ip,j,bj,jp) =
216 & globfld3d(i,bi,ip,j,bj,jp,k)
217 cph)
218 enddo
219 enddo
220 enddo
221 enddo
222 enddo
223 enddo
224 cph(
225 if ( doPackDiag ) then
226 write(cunit2,rec=irectrue) globfldtmp2
227 write(cunit3,rec=irectrue) globfldtmp3
228 endif
229 cph)
230 enddo
231
232 call MDSWRITEFIELD_3D_GL( fname, ctrlprec, 'RL',
233 & NR, globfld3d,
234 & irec, optimcycle, mythid)
235
236 enddo
237
238 do irec = nrec_nl*Nr+1,ncvarrecs(ivartype)
239 print *, 'ph-pack nrec_nl+irec ', irec, nrec_nl, ivartype,
240 & ncvarrecs(ivartype)
241 #ifndef ALLOW_ADMTLM
242 read(cunit) filencvarindex(ivartype)
243 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
244 & then
245 print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
246 & filencvarindex(ivartype), ncvarindex(ivartype)
247 STOP 'in S/R ctrl_unpack'
248 endif
249 read(cunit) filej
250 read(cunit) filei
251 #endif /* ndef ALLOW_ADMTLM */
252 do k = 1,1
253 irectrue = irec
254 cbuffindex = nwetglobal(k)
255 #ifndef ALLOW_ADMTLM
256 if ( cbuffindex .gt. 0 ) then
257 read(cunit) filencbuffindex
258 if (filencbuffindex .NE. cbuffindex) then
259 print *, 'WARNING: wrong cbuffindex ',
260 & filencbuffindex, cbuffindex
261 STOP 'in S/R ctrl_unpack'
262 endif
263 read(cunit) filek
264 if (filek .NE. k) then
265 print *, 'WARNING: wrong k ',
266 & filek, k
267 STOP 'in S/R ctrl_unpack'
268 endif
269 read(cunit) (cbuff(ii), ii=1,cbuffindex)
270 endif
271 #else ALLOW_ADMTLM
272 write(fnameGlobal(1:80),'(a)') ' '
273 write(fnameGlobal,'(a,i4.4)')
274 & 'admtlm_vector.it', optimcycle
275 call mdsreadvector( fnameGlobal, 64, 'RL',
276 & admtlmrec, cbuffGlobal, 1, 1, nbuffGlobal, mythid )
277 do ii = 1, cbuffindex
278 cbuff(ii) = cbuffGlobal(ii)
279 enddo
280 #endif
281 cbuffindex = 0
282 do jp = 1,nPy
283 do bj = jtlo,jthi
284 do j = jmin,jmax
285 do ip = 1,nPx
286 do bi = itlo,ithi
287 do i = imin,imax
288 if ( globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
289 cbuffindex = cbuffindex + 1
290 globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
291 cph(
292 globfldtmp2(i,bi,ip,j,bj,jp) = cbuff(cbuffindex)
293 cph)
294 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
295 if ( lxxadxx ) then
296 globfld3d(i,bi,ip,j,bj,jp,k) =
297 & globfld3d(i,bi,ip,j,bj,jp,k)/
298 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
299 else
300 globfld3d(i,bi,ip,j,bj,jp,k) =
301 & globfld3d(i,bi,ip,j,bj,jp,k)*
302 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
303 endif
304 #endif
305 else
306 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
307 endif
308 cph(
309 globfldtmp3(i,bi,ip,j,bj,jp) =
310 & globfld3d(i,bi,ip,j,bj,jp,k)
311 cph)
312 enddo
313 enddo
314 enddo
315 enddo
316 enddo
317 enddo
318 cph(
319 if ( doPackDiag ) then
320 write(cunit2,rec=irectrue) globfldtmp2
321 write(cunit3,rec=irectrue) globfldtmp3
322 endif
323 cph)
324 enddo
325
326 call MDSWRITEFIELD_2D_GL( fname, ctrlprec, 'RL',
327 & 1, globfld3d(1,1,1,1,1,1,1),
328 & irec, optimcycle, mythid)
329
330 enddo
331
332 if ( doPackDiag ) then
333 close ( cunit2 )
334 close ( cunit3 )
335 endif
336
337 _END_MASTER( mythid )
338
339 return
340 end
341

  ViewVC Help
Powered by ViewVC 1.1.22