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

Annotation of /MITgcm/pkg/ctrl/ctrl_set_unpack_xz.F

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


Revision 1.19 - (hide annotations) (download)
Thu Oct 9 00:49:27 2014 UTC (9 years, 8 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint65z, checkpoint65x, checkpoint65y, checkpoint65r, checkpoint65s, checkpoint65p, checkpoint65q, checkpoint65v, checkpoint65w, checkpoint65t, checkpoint65u, checkpoint65j, checkpoint65k, checkpoint65h, checkpoint65i, checkpoint65n, checkpoint65l, checkpoint65m, checkpoint65f, checkpoint65g, checkpoint66g, checkpoint66f, checkpoint66e, checkpoint66d, checkpoint66c, checkpoint66b, checkpoint66a, checkpoint66o, checkpoint66n, checkpoint66m, checkpoint66l, checkpoint66k, checkpoint66j, checkpoint66i, checkpoint66h, checkpoint65o, HEAD
Changes since 1.18: +2 -1 lines
- pkg/ctrl/CTRL_OBCS.h (new) : regroup all obcs ctrl variables.
- pkg/ctrl/ctrl.h, ctrl_dummy.h, ctrl_weights.h : rm obcs
  ctrl variables (now all in CTRL_OBCS.h).

- pkg/ctrl/ctrl_getobcse.F, ctrl_getobcsn.F, ctrl_getobcss.F,
  ctrl_getobcsw.F, ctrl_getrec.F, ctrl_init.F, ctrl_init_obcs_variables.F,
  ctrl_init_wet.F, ctrl_mask_set_xz.F, ctrl_mask_set_yz.F,
  ctrl_pack.F, ctrl_unpack.F, ctrl_readparms.F,
  ctrl_set_pack_xz.F, ctrl_set_pack_yz.F, ctrl_set_unpack_xz.F,
  ctrl_set_unpack_yz.F : add CPP brackets and CTRL_OBCS.h

- pkg/ctrl/ctrl_pack.F, ctrl_unpack.F : add CPP brackets

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

  ViewVC Help
Powered by ViewVC 1.1.22