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

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

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


Revision 1.18 - (hide annotations) (download)
Tue Jun 19 03:42:30 2007 UTC (16 years, 11 months ago) by gforget
Branch: MAIN
CVS Tags: checkpoint59e, checkpoint59d, checkpoint59g, checkpoint59f, checkpoint59h
Changes since 1.17: +4 -0 lines
pkg/smooth application to control vector

1 heimbach 1.2
2     #include "CTRL_CPPOPTIONS.h"
3    
4     subroutine ctrl_set_pack_xyz(
5 heimbach 1.4 & cunit, ivartype, fname, masktype, weighttype,
6 heimbach 1.2 & weightfld, lxxadxx, mythid)
7    
8     c ==================================================================
9     c SUBROUTINE ctrl_set_pack_xyz
10     c ==================================================================
11     c
12     c o Compress the control vector such that only ocean points are
13     c written to file.
14     c
15 heimbach 1.4 c o Use a more precise nondimensionalization that depends on (x,y)
16     c Added weighttype to the argument list so that I can geographically
17     c vary the nondimensionalization.
18     c gebbie@mit.edu, 18-Mar-2003
19     c
20 heimbach 1.2 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     integer cunit
37     integer ivartype
38     character*( 80) fname
39 heimbach 1.11 character*( 9) masktype
40 heimbach 1.4 character*( 80) weighttype
41 heimbach 1.2 _RL weightfld( nr,nsx,nsy )
42     logical lxxadxx
43     integer mythid
44    
45 heimbach 1.17 #ifndef EXCLUDE_CTRL_PACK
46 heimbach 1.2 c == local variables ==
47    
48     integer bi,bj
49     integer ip,jp
50     integer i,j,k
51     integer ii
52     integer il
53     integer irec
54     integer itlo,ithi
55     integer jtlo,jthi
56     integer jmin,jmax
57     integer imin,imax
58    
59     integer cbuffindex
60    
61     _RL globmsk ( snx,nsx,npx,sny,nsy,npy,nr )
62     _RL globfld3d( snx,nsx,npx,sny,nsy,npy,nr )
63 heimbach 1.4 #ifdef CTRL_PACK_PRECISE
64     _RL weightfld3d( snx,nsx,npx,sny,nsy,npy,nr )
65     #endif
66 heimbach 1.9 real*4 cbuff ( snx*nsx*npx*sny*nsy*npy )
67     real*4 globfldtmp2( snx,nsx,npx,sny,nsy,npy )
68     real*4 globfldtmp3( snx,nsx,npx,sny,nsy,npy )
69 heimbach 1.4
70     character*(80) weightname
71 heimbach 1.2
72 heimbach 1.9 _RL delZnorm
73     integer reclen, irectrue
74     integer cunit2, cunit3
75     character*(80) cfile2, cfile3
76    
77 heimbach 1.2 c == external ==
78    
79     integer ilnblnk
80     external ilnblnk
81    
82     c == 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 heimbach 1.9 #ifdef CTRL_DELZNORM
94     delZnorm = 0.
95     do k = 1, Nr
96     delZnorm = delZnorm + delR(k)/FLOAT(Nr)
97     enddo
98     #endif
99    
100 heimbach 1.2 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 heimbach 1.9 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 heimbach 1.2 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 heimbach 1.9 if ( doPackDiag ) then
124     write(cfile2(1:80),'(80a)') ' '
125     write(cfile3(1:80),'(80a)') ' '
126     if ( lxxadxx ) then
127     write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
128     & 'diag_pack_nonout_ctrl_',
129     & ivartype, '_', optimcycle, '.bin'
130     write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
131     & 'diag_pack_dimout_ctrl_',
132     & ivartype, '_', optimcycle, '.bin'
133     else
134     write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
135     & 'diag_pack_nonout_grad_',
136     & ivartype, '_', optimcycle, '.bin'
137     write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
138     & 'diag_pack_dimout_grad_',
139     & ivartype, '_', optimcycle, '.bin'
140     endif
141    
142     reclen = FLOAT(snx*nsx*npx*sny*nsy*npy*4)
143     call mdsfindunit( cunit2, mythid )
144     open( cunit2, file=cfile2, status='unknown',
145     & access='direct', recl=reclen )
146     call mdsfindunit( cunit3, mythid )
147     open( cunit3, file=cfile3, status='unknown',
148     & access='direct', recl=reclen )
149     endif
150    
151 heimbach 1.4 #ifdef CTRL_PACK_PRECISE
152     il=ilnblnk( weighttype)
153     write(weightname(1:80),'(80a)') ' '
154     write(weightname(1:80),'(a)') weighttype(1:il)
155    
156     call MDSREADFIELD_3D_GL(
157     & weightname, ctrlprec, 'RL',
158     & Nr, weightfld3d, 1, mythid)
159     #endif
160    
161 heimbach 1.2 call MDSREADFIELD_3D_GL(
162     & masktype, ctrlprec, 'RL',
163     & Nr, globmsk, 1, mythid)
164    
165     do irec = 1, ncvarrecs(ivartype)
166    
167     call MDSREADFIELD_3D_GL( fname, ctrlprec, 'RL',
168     & Nr, globfld3d, irec, mythid)
169    
170 heimbach 1.13 #ifndef ALLOW_ADMTLM
171 heimbach 1.2 write(cunit) ncvarindex(ivartype)
172     write(cunit) 1
173     write(cunit) 1
174 heimbach 1.13 #endif
175 heimbach 1.2 do k = 1, nr
176 heimbach 1.9 irectrue = (irec-1)*nr + k
177 heimbach 1.10 if ( doZscalePack ) then
178 heimbach 1.15 delZnorm = (delR(1)/delR(k))**delZexp
179 heimbach 1.10 else
180     delZnorm = 1. _d 0
181     endif
182 heimbach 1.2 cbuffindex = 0
183     do jp = 1,nPy
184     do bj = jtlo,jthi
185     do j = jmin,jmax
186     do ip = 1,nPx
187     do bi = itlo,ithi
188     do i = imin,imax
189 heimbach 1.9 if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
190 heimbach 1.2 cbuffindex = cbuffindex + 1
191 heimbach 1.9 cph(
192     globfldtmp3(i,bi,ip,j,bj,jp) =
193     & globfld3d(i,bi,ip,j,bj,jp,k)
194     cph)
195 gforget 1.18 #ifndef ALLOW_SMOOTH_CORREL3D
196 heimbach 1.2 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
197     if (lxxadxx) then
198 gforget 1.16 cbuff(cbuffindex) = 1/delZnorm
199 heimbach 1.10 & * globfld3d(i,bi,ip,j,bj,jp,k)
200 heimbach 1.4 # ifdef CTRL_PACK_PRECISE
201 heimbach 1.9 & * sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
202 heimbach 1.4 # else
203 heimbach 1.9 & * sqrt(weightfld(k,bi,bj))
204 heimbach 1.4 # endif
205 heimbach 1.2 else
206 heimbach 1.10 cbuff(cbuffindex) = delZnorm
207     & * globfld3d(i,bi,ip,j,bj,jp,k)
208 heimbach 1.4 # ifdef CTRL_PACK_PRECISE
209 heimbach 1.9 & / sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
210 heimbach 1.4 # else
211 heimbach 1.9 & / sqrt(weightfld(k,bi,bj))
212 heimbach 1.4 # endif
213 heimbach 1.2 endif
214 heimbach 1.9 cph(
215     globfldtmp2(i,bi,ip,j,bj,jp) = cbuff(cbuffindex)
216     cph)
217 heimbach 1.4 #else /* ALLOW_NONDIMENSIONAL_CONTROL_IO undef */
218 heimbach 1.2 cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
219 heimbach 1.4 #endif /* ALLOW_NONDIMENSIONAL_CONTROL_IO */
220 gforget 1.18 #else /* ALLOW_SMOOTH_CORREL3D */
221     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
222     #endif /* ALLOW_SMOOTH_CORREL3D */
223 heimbach 1.13 #ifdef ALLOW_ADMTLM
224     nveccount = nveccount + 1
225     phtmpadmtlm(nveccount) = cbuff(cbuffindex)
226     #endif
227 heimbach 1.2 endif
228     enddo
229     enddo
230     enddo
231     enddo
232     enddo
233     enddo
234     c --> check cbuffindex.
235     if ( cbuffindex .gt. 0) then
236 heimbach 1.13 #ifndef ALLOW_ADMTLM
237 heimbach 1.2 write(cunit) cbuffindex
238     write(cunit) k
239 heimbach 1.14 cph#endif
240     write(cunit) (cbuff(ii), ii=1,cbuffindex)
241 heimbach 1.13 #endif
242 heimbach 1.2 endif
243 heimbach 1.9 c
244     if ( doPackDiag ) then
245     write(cunit2,rec=irectrue) globfldtmp2
246     write(cunit3,rec=irectrue) globfldtmp3
247     endif
248     c
249 heimbach 1.2 enddo
250     c
251     c -- end of irec loop --
252     enddo
253    
254 heimbach 1.9 if ( doPackDiag ) then
255     close ( cunit2 )
256     close ( cunit3 )
257     endif
258    
259 heimbach 1.2 _END_MASTER( mythid )
260    
261 heimbach 1.17 #endif
262    
263 heimbach 1.2 return
264     end
265    

  ViewVC Help
Powered by ViewVC 1.1.22