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

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

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


Revision 1.10 - (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.9: +13 -10 lines
o introduce z-scaling of
  * gradient (doZscalePack) and
  * control (doZscaleUnpack)

1
2 #include "CTRL_CPPOPTIONS.h"
3
4 subroutine ctrl_set_unpack_xyz(
5 & lxxadxx, cunit, ivartype, fname, masktype, weighttype,
6 & weightfld, nwetglobal, mythid)
7
8 c ==================================================================
9 c SUBROUTINE ctrl_set_unpack_xyz
10 c ==================================================================
11 c
12 c o Unpack the control vector such that land points are filled in.
13 c
14 c o Use a more precise nondimensionalization that depends on (x,y)
15 c Added weighttype to the argument list so that I can geographically
16 c vary the nondimensionalization.
17 c gebbie@mit.edu, 18-Mar-2003
18 c
19 c ==================================================================
20
21 implicit none
22
23 c == global variables ==
24
25 #include "EEPARAMS.h"
26 #include "SIZE.h"
27 #include "PARAMS.h"
28 #include "GRID.h"
29
30 #include "ctrl.h"
31 #include "optim.h"
32
33 c == routine arguments ==
34
35 logical lxxadxx
36 integer cunit
37 integer ivartype
38 character*( 80) fname
39 character* (5) masktype
40 character*( 80) weighttype
41 _RL weightfld( nr,nsx,nsy )
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
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 #ifdef CTRL_UNPACK_PRECISE
63 _RL weightfld3d( snx,nsx,npx,sny,nsy,npy,nr )
64 #endif
65 real*4 cbuff ( snx*nsx*npx*sny*nsy*npy )
66 real*4 globfldtmp2( snx,nsx,npx,sny,nsy,npy )
67 real*4 globfldtmp3( snx,nsx,npx,sny,nsy,npy )
68
69 character*(128) cfile
70 character*(80) weightname
71
72 _RL delZnorm
73 integer reclen, irectrue
74 integer cunit2, cunit3
75 character*(80) cfile2, cfile3
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 #ifdef CTRL_DELZNORM
94 delZnorm = 0.
95 do k = 1, Nr
96 delZnorm = delZnorm + delR(k)/FLOAT(Nr)
97 enddo
98 #endif
99
100 c Initialise temporary file
101 do k = 1,nr
102 do jp = 1,nPy
103 do bj = jtlo,jthi
104 do j = jmin,jmax
105 do ip = 1,nPx
106 do bi = itlo,ithi
107 do i = imin,imax
108 globfld3d (i,bi,ip,j,bj,jp,k) = 0. _d 0
109 globmsk (i,bi,ip,j,bj,jp,k) = 0. _d 0
110 globfldtmp2(i,bi,ip,j,bj,jp) = 0.
111 globfldtmp3(i,bi,ip,j,bj,jp) = 0.
112 enddo
113 enddo
114 enddo
115 enddo
116 enddo
117 enddo
118 enddo
119
120 c-- Only the master thread will do I/O.
121 _BEGIN_MASTER( mythid )
122
123 #ifdef CTRL_DELZNORM
124 do k = 1, nr
125 print *, 'ph-delznorm ', k, delZnorm, delR(k)
126 print *, 'ph-weight ', weightfld(k,1,1)
127 enddo
128 #endif
129
130 if ( doPackDiag ) then
131 write(cfile2(1:80),'(80a)') ' '
132 write(cfile3(1:80),'(80a)') ' '
133 if ( lxxadxx ) then
134 write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
135 & 'diag_unpack_nondim_ctrl_',
136 & ivartype, '_', optimcycle, '.bin'
137 write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
138 & 'diag_unpack_dimens_ctrl_',
139 & ivartype, '_', optimcycle, '.bin'
140 else
141 write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
142 & 'diag_unpack_nondim_grad_',
143 & ivartype, '_', optimcycle, '.bin'
144 write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
145 & 'diag_unpack_dimens_grad_',
146 & ivartype, '_', optimcycle, '.bin'
147 endif
148
149 reclen = FLOAT(snx*nsx*npx*sny*nsy*npy*4)
150 call mdsfindunit( cunit2, mythid )
151 open( cunit2, file=cfile2, status='unknown',
152 & access='direct', recl=reclen )
153 call mdsfindunit( cunit3, mythid )
154 open( cunit3, file=cfile3, status='unknown',
155 & access='direct', recl=reclen )
156 endif
157
158 #ifdef CTRL_UNPACK_PRECISE
159 il=ilnblnk( weighttype)
160 write(weightname(1:80),'(80a)') ' '
161 write(weightname(1:80),'(a)') weighttype(1:il)
162
163 call MDSREADFIELD_3D_GL(
164 & weightname, ctrlprec, 'RL',
165 & Nr, weightfld3d, 1, mythid)
166 #endif
167
168 call MDSREADFIELD_3D_GL(
169 & masktype, ctrlprec, 'RL',
170 & Nr, globmsk, 1, mythid)
171
172 do irec = 1, ncvarrecs(ivartype)
173 read(cunit) filencvarindex(ivartype)
174 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
175 & then
176 print *, 'ctrl_set_unpack_xyz:WARNING: wrong ncvarindex ',
177 & filencvarindex(ivartype), ncvarindex(ivartype)
178 STOP 'in S/R ctrl_unpack'
179 endif
180 read(cunit) filej
181 read(cunit) filei
182 do k = 1, Nr
183 irectrue = (irec-1)*nr + k
184 if ( doZscaleUnpack ) then
185 delZnorm = SQRT(delR(1)/delR(k))
186 else
187 delZnorm = 1. _d 0
188 endif
189 cbuffindex = nwetglobal(k)
190 if ( cbuffindex .gt. 0 ) then
191 read(cunit) filencbuffindex
192 if (filencbuffindex .NE. cbuffindex) then
193 print *, 'WARNING: wrong cbuffindex ',
194 & filencbuffindex, cbuffindex
195 STOP 'in S/R ctrl_unpack'
196 endif
197 read(cunit) filek
198 if (filek .NE. k) then
199 print *, 'WARNING: wrong k ',
200 & filek, k
201 STOP 'in S/R ctrl_unpack'
202 endif
203 read(cunit) (cbuff(ii), ii=1,cbuffindex)
204 endif
205 cbuffindex = 0
206 do jp = 1,nPy
207 do bj = jtlo,jthi
208 do j = jmin,jmax
209 do ip = 1,nPx
210 do bi = itlo,ithi
211 do i = imin,imax
212 if ( globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
213 cbuffindex = cbuffindex + 1
214 globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
215 cph(
216 globfldtmp2(i,bi,ip,j,bj,jp) = cbuff(cbuffindex)
217 cph)
218 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
219 if ( lxxadxx ) then
220 globfld3d(i,bi,ip,j,bj,jp,k) = delZnorm
221 & * globfld3d(i,bi,ip,j,bj,jp,k)
222 # ifdef CTRL_UNPACK_PRECISE
223 & / sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
224 # else
225 & / sqrt(weightfld(k,bi,bj))
226 # endif
227 else
228 globfld3d(i,bi,ip,j,bj,jp,k) = delZnorm
229 & * globfld3d(i,bi,ip,j,bj,jp,k)
230 # ifdef CTRL_UNPACK_PRECISE
231 & * sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
232 # else
233 & * sqrt(weightfld(k,bi,bj))
234 # endif
235 endif
236 #endif /* ALLOW_NONDIMENSIONAL_CONTROL_IO */
237 else
238 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
239 endif
240 cph(
241 globfldtmp3(i,bi,ip,j,bj,jp) =
242 & globfld3d(i,bi,ip,j,bj,jp,k)
243 cph)
244 enddo
245 enddo
246 enddo
247 enddo
248 enddo
249 enddo
250 c
251 if ( doPackDiag ) then
252 write(cunit2,rec=irectrue) globfldtmp2
253 write(cunit3,rec=irectrue) globfldtmp3
254 endif
255 c
256 enddo
257
258 call MDSWRITEFIELD_3D_GL( fname, ctrlprec, 'RL',
259 & Nr, globfld3d,
260 & irec, optimcycle, mythid)
261
262 enddo
263
264 if ( doPackDiag ) then
265 close ( cunit2 )
266 close ( cunit3 )
267 endif
268
269 _END_MASTER( mythid )
270
271 return
272 end
273

  ViewVC Help
Powered by ViewVC 1.1.22