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

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

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


Revision 1.11 - (show annotations) (download)
Thu Jun 14 18:55:36 2007 UTC (16 years, 11 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59h
Changes since 1.10: +3 -0 lines
Exclude global arrays if we dont need/want them
(thought we had checked this in a while ago, but apparently not)

1
2 #include "CTRL_CPPOPTIONS.h"
3
4 subroutine ctrl_set_unpack_yz(
5 & cunit, ivartype, fname, masktype, weighttype,
6 & weightfld, nwetglobal, mythid)
7
8 c ==================================================================
9 c SUBROUTINE ctrl_set_unpack_yz
10 c ==================================================================
11 c
12 c o Unpack the control vector such that land points are filled in.
13 c
14 c o Open boundary packing added :
15 c gebbie@mit.edu, 18-Mar-2003
16 c
17 c changed: heimbach@mit.edu 17-Jun-2003
18 c merged Armin's changes to replace write of
19 c nr * globfld2d by 1 * globfld3d
20 c (ad hoc fix to speed up global I/O)
21 c
22 c ==================================================================
23
24 implicit none
25
26 c == global variables ==
27
28 #include "EEPARAMS.h"
29 #include "SIZE.h"
30 #include "PARAMS.h"
31 #include "GRID.h"
32
33 #include "ctrl.h"
34 #include "optim.h"
35
36 c == routine arguments ==
37
38 integer cunit
39 integer ivartype
40 character*( 80) fname
41 character* (9) masktype
42 character*( 80) weighttype
43 _RL weightfld( nr,nobcs )
44 integer nwetglobal(nr,nobcs)
45 integer mythid
46
47 #ifndef EXCLUDE_CTRL_PACK
48 c == local variables ==
49
50 integer bi,bj
51 integer ip,jp
52 integer i,j,k
53 integer ii,jj,kk
54 integer il
55 integer irec,iobcs,nrec_nl
56 integer itlo,ithi
57 integer jtlo,jthi
58 integer jmin,jmax
59 integer imin,imax
60
61 integer cbuffindex
62
63 real*4 cbuff ( nsx*npx*sny*nsy*npy )
64 _RL globfldyz( nsx,npx,sny,nsy,npy,nr )
65 _RL globfld3d( snx,nsx,npx,sny,nsy,npy,nr )
66 _RL globmskyz( nsx,npx,sny,nsy,npy,nr,nobcs )
67 #ifdef CTRL_UNPACK_PRECISE
68 _RL weightfldyz( nsx,npx,sny,nsy,npy,nr,nobcs )
69 #endif
70
71 cgg(
72 integer igg
73 _RL gg
74 character*(80) weightname
75 cgg)
76
77 c == external ==
78
79 integer ilnblnk
80 external ilnblnk
81
82 cc == end of interface ==
83
84 jtlo = 1
85 jthi = nsy
86 itlo = 1
87 ithi = nsx
88 jmin = 1
89 jmax = sny
90 imin = 1
91 imax = snx
92
93 c Initialise temporary file
94 do k = 1,nr
95 do jp = 1,nPy
96 do bj = jtlo,jthi
97 do j = jmin,jmax
98 do ip = 1,nPx
99 do bi = itlo,ithi
100 globfldyz(bi,ip,j,bj,jp,k) = 0. _d 0
101 do iobcs=1,nobcs
102 globmskyz(bi,ip,j,bj,jp,k,iobcs) = 0. _d 0
103 enddo
104 enddo
105 enddo
106 enddo
107 enddo
108 enddo
109 enddo
110 c Initialise temporary file
111 do k = 1,nr
112 do jp = 1,nPy
113 do bj = jtlo,jthi
114 do j = jmin,jmax
115 do ip = 1,nPx
116 do bi = itlo,ithi
117 do i = imin,imax
118 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
119 enddo
120 enddo
121 enddo
122 enddo
123 enddo
124 enddo
125 enddo
126
127 c-- Only the master thread will do I/O.
128 _BEGIN_MASTER( mythid )
129
130 do iobcs=1,nobcs
131 call MDSREADFIELD_YZ_GL(
132 & masktype, ctrlprec, 'RL',
133 & Nr, globmskyz(1,1,1,1,1,1,iobcs), iobcs, mythid)
134 #ifdef CTRL_UNPACK_PRECISE
135 il=ilnblnk( weighttype)
136 write(weightname(1:80),'(80a)') ' '
137 write(weightname(1:80),'(a)') weighttype(1:il)
138 call MDSREADFIELD_YZ_GL(
139 & weightname, ctrlprec, 'RL',
140 & Nr, weightfldyz(1,1,1,1,1,1,iobcs), iobcs, mythid)
141 CGG One special exception: barotropic velocity should be nondimensionalized
142 cgg differently. Probably introduce new variable.
143 if (iobcs .eq. 3 .or. iobcs .eq. 4) then
144 k = 1
145 do jp = 1,nPy
146 do bj = jtlo,jthi
147 do j = jmin,jmax
148 do ip = 1,nPx
149 do bi = itlo,ithi
150 cph weightfldyz(bi,ip,j,bj,jp,k,iobcs) = wbaro
151 enddo
152 enddo
153 enddo
154 enddo
155 enddo
156 endif
157 #endif
158 enddo
159
160 nrec_nl=int(ncvarrecs(ivartype)/snx)
161 do irec = 1, nrec_nl
162 cgg do iobcs = 1, nobcs
163 cgg And now back-calculate what iobcs should be.
164 do i=1,snx
165 iobcs= mod((irec-1)*snx+i-1,nobcs)+1
166
167 read(cunit) filencvarindex(ivartype)
168 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
169 & then
170 print *, 'ctrl_set_unpack_yz:WARNING: wrong ncvarindex ',
171 & filencvarindex(ivartype), ncvarindex(ivartype)
172 STOP 'in S/R ctrl_unpack'
173 endif
174 read(cunit) filej
175 read(cunit) filei
176 do k = 1, Nr
177 cbuffindex = nwetglobal(k,iobcs)
178 if ( cbuffindex .gt. 0 ) then
179 read(cunit) filencbuffindex
180 if (filencbuffindex .NE. cbuffindex) then
181 print *, 'WARNING: wrong cbuffindex ',
182 & filencbuffindex, cbuffindex
183 STOP 'in S/R ctrl_unpack'
184 endif
185 read(cunit) filek
186 if (filek .NE. k) then
187 print *, 'WARNING: wrong k ',
188 & filek, k
189 STOP 'in S/R ctrl_unpack'
190 endif
191 read(cunit) (cbuff(ii), ii=1,cbuffindex)
192 endif
193 cbuffindex = 0
194 do jp = 1,nPy
195 do bj = jtlo,jthi
196 do j = jmin,jmax
197 do ip = 1,nPx
198 do bi = itlo,ithi
199 ii=mod((i-1)*nr*sny+(k-1)*sny+j-1,snx)+1
200 jj=mod(((i-1)*nr*sny+(k-1)*sny+j-1)/snx,sny)+1
201 kk=int((i-1)*nr*sny+(k-1)*sny+j-1)/(snx*sny)+1
202 if ( globmskyz(bi,ip,j,bj,jp,k,iobcs) .ne. 0. ) then
203 cbuffindex = cbuffindex + 1
204 globfld3d(ii,bi,ip,jj,bj,jp,kk) =
205 & cbuff(cbuffindex)
206 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
207 globfld3d(ii,bi,ip,jj,bj,jp,kk) =
208 & globfld3d(ii,bi,ip,jj,bj,jp,kk)/
209 # ifdef CTRL_UNPACK_PRECISE
210 & sqrt(weightfldyz(bi,ip,j,bj,jp,k,iobcs))
211 # else
212 & sqrt(weightfld(k,iobcs))
213 # endif
214 #endif /* ALLOW_NONDIMENSIONAL_CONTROL_IO */
215 else
216 globfld3d(ii,bi,ip,jj,bj,jp,kk) = 0. _d 0
217 endif
218 enddo
219 enddo
220 enddo
221 enddo
222 enddo
223 c
224 c -- end of k loop --
225 enddo
226 c -- end of i loop --
227 enddo
228
229 call MDSWRITEFIELD_3d_GL( fname, ctrlprec, 'RL',
230 & Nr, globfld3d, irec,
231 & optimcycle, mythid)
232
233 c -- end of iobcs loop -- This loop has been removed.
234 cgg enddo
235 c -- end of irec loop --
236 enddo
237
238 do irec = nrec_nl*snx+1,ncvarrecs(ivartype)
239 iobcs= mod(irec-1,nobcs)+1
240
241 read(cunit) filencvarindex(ivartype)
242 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
243 & then
244 print *, 'ctrl_set_unpack_yz:WARNING: wrong ncvarindex ',
245 & filencvarindex(ivartype), ncvarindex(ivartype)
246 STOP 'in S/R ctrl_unpack'
247 endif
248 read(cunit) filej
249 read(cunit) filei
250 do k = 1, Nr
251 cbuffindex = nwetglobal(k,iobcs)
252 if ( cbuffindex .gt. 0 ) then
253 read(cunit) filencbuffindex
254 if (filencbuffindex .NE. cbuffindex) then
255 print *, 'WARNING: wrong cbuffindex ',
256 & filencbuffindex, cbuffindex
257 STOP 'in S/R ctrl_unpack'
258 endif
259 read(cunit) filek
260 if (filek .NE. k) then
261 print *, 'WARNING: wrong k ',
262 & filek, k
263 STOP 'in S/R ctrl_unpack'
264 endif
265 read(cunit) (cbuff(ii), ii=1,cbuffindex)
266 endif
267 cbuffindex = 0
268 do jp = 1,nPy
269 do bj = jtlo,jthi
270 do j = jmin,jmax
271 do ip = 1,nPx
272 do bi = itlo,ithi
273 if ( globmskyz(bi,ip,j,bj,jp,k,iobcs) .ne. 0. ) then
274 cbuffindex = cbuffindex + 1
275 globfldyz(bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
276 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
277 globfldyz(bi,ip,j,bj,jp,k) =
278 & globfldyz(bi,ip,j,bj,jp,k)/
279 # ifdef CTRL_UNPACK_PRECISE
280 & sqrt(weightfldyz(bi,ip,j,bj,jp,k,iobcs))
281 # else
282 & sqrt(weightfld(k,iobcs))
283 # endif
284 #endif /* ALLOW_NONDIMENSIONAL_CONTROL_IO */
285 else
286 globfldyz(bi,ip,j,bj,jp,k) = 0. _d 0
287 endif
288 enddo
289 enddo
290 enddo
291 enddo
292 enddo
293 c
294 c -- end of k loop
295 enddo
296
297 call MDSWRITEFIELD_YZ_GL( fname, ctrlprec, 'RL',
298 & Nr, globfldyz, irec,
299 & optimcycle, mythid)
300
301 c -- end of iobcs loop -- This loop has been removed.
302 cgg enddo
303 c -- end of irec loop --
304 enddo
305
306 _END_MASTER( mythid )
307
308 #endif
309
310 return
311 end
312

  ViewVC Help
Powered by ViewVC 1.1.22