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

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

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


Revision 1.17 - (hide annotations) (download)
Thu Jun 14 18:55:36 2007 UTC (16 years, 11 months ago) by heimbach
Branch: MAIN
Changes since 1.16: +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 heimbach 1.2
2     #include "CTRL_CPPOPTIONS.h"
3    
4     subroutine ctrl_set_unpack_xyz(
5 heimbach 1.9 & lxxadxx, cunit, ivartype, fname, masktype, weighttype,
6 heimbach 1.2 & weightfld, nwetglobal, mythid)
7    
8     c ==================================================================
9     c SUBROUTINE ctrl_set_unpack_xyz
10     c ==================================================================
11     c
12 heimbach 1.3 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 heimbach 1.2 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 heimbach 1.9 logical lxxadxx
36 heimbach 1.2 integer cunit
37     integer ivartype
38     character*( 80) fname
39 heimbach 1.11 character*( 9) masktype
40 heimbach 1.3 character*( 80) weighttype
41 heimbach 1.2 _RL weightfld( nr,nsx,nsy )
42     integer nwetglobal(nr)
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.3 #ifdef CTRL_UNPACK_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.2
70     character*(128) cfile
71 heimbach 1.3 character*(80) weightname
72 heimbach 1.2
73 heimbach 1.9 _RL delZnorm
74     integer reclen, irectrue
75     integer cunit2, cunit3
76     character*(80) cfile2, cfile3
77    
78 heimbach 1.2 c == external ==
79    
80     integer ilnblnk
81     external ilnblnk
82    
83     cc == end of interface ==
84    
85     jtlo = 1
86     jthi = nsy
87     itlo = 1
88     ithi = nsx
89     jmin = 1
90     jmax = sny
91     imin = 1
92     imax = snx
93    
94 heimbach 1.9 #ifdef CTRL_DELZNORM
95     delZnorm = 0.
96     do k = 1, Nr
97     delZnorm = delZnorm + delR(k)/FLOAT(Nr)
98     enddo
99     #endif
100    
101 heimbach 1.2 c Initialise temporary file
102     do k = 1,nr
103     do jp = 1,nPy
104     do bj = jtlo,jthi
105     do j = jmin,jmax
106     do ip = 1,nPx
107     do bi = itlo,ithi
108     do i = imin,imax
109 heimbach 1.9 globfld3d (i,bi,ip,j,bj,jp,k) = 0. _d 0
110     globmsk (i,bi,ip,j,bj,jp,k) = 0. _d 0
111     globfldtmp2(i,bi,ip,j,bj,jp) = 0.
112     globfldtmp3(i,bi,ip,j,bj,jp) = 0.
113 heimbach 1.2 enddo
114     enddo
115     enddo
116     enddo
117     enddo
118     enddo
119     enddo
120    
121     c-- Only the master thread will do I/O.
122     _BEGIN_MASTER( mythid )
123    
124 heimbach 1.9 #ifdef CTRL_DELZNORM
125     do k = 1, nr
126     print *, 'ph-delznorm ', k, delZnorm, delR(k)
127     print *, 'ph-weight ', weightfld(k,1,1)
128     enddo
129     #endif
130    
131     if ( doPackDiag ) then
132     write(cfile2(1:80),'(80a)') ' '
133     write(cfile3(1:80),'(80a)') ' '
134     if ( lxxadxx ) then
135     write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
136     & 'diag_unpack_nondim_ctrl_',
137     & ivartype, '_', optimcycle, '.bin'
138     write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
139     & 'diag_unpack_dimens_ctrl_',
140     & ivartype, '_', optimcycle, '.bin'
141     else
142     write(cfile2(1:80),'(a,I2.2,a,I4.4,a)')
143     & 'diag_unpack_nondim_grad_',
144     & ivartype, '_', optimcycle, '.bin'
145     write(cfile3(1:80),'(a,I2.2,a,I4.4,a)')
146     & 'diag_unpack_dimens_grad_',
147     & ivartype, '_', optimcycle, '.bin'
148     endif
149    
150     reclen = FLOAT(snx*nsx*npx*sny*nsy*npy*4)
151     call mdsfindunit( cunit2, mythid )
152 heimbach 1.10 open( cunit2, file=cfile2, status='unknown',
153 heimbach 1.9 & access='direct', recl=reclen )
154     call mdsfindunit( cunit3, mythid )
155 heimbach 1.10 open( cunit3, file=cfile3, status='unknown',
156 heimbach 1.9 & access='direct', recl=reclen )
157     endif
158    
159 heimbach 1.3 #ifdef CTRL_UNPACK_PRECISE
160     il=ilnblnk( weighttype)
161     write(weightname(1:80),'(80a)') ' '
162     write(weightname(1:80),'(a)') weighttype(1:il)
163    
164     call MDSREADFIELD_3D_GL(
165     & weightname, ctrlprec, 'RL',
166     & Nr, weightfld3d, 1, mythid)
167     #endif
168    
169 heimbach 1.2 call MDSREADFIELD_3D_GL(
170     & masktype, ctrlprec, 'RL',
171     & Nr, globmsk, 1, mythid)
172    
173     do irec = 1, ncvarrecs(ivartype)
174 heimbach 1.13 #ifndef ALLOW_ADMTLM
175 heimbach 1.2 read(cunit) filencvarindex(ivartype)
176     if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
177     & then
178     print *, 'ctrl_set_unpack_xyz:WARNING: wrong ncvarindex ',
179     & filencvarindex(ivartype), ncvarindex(ivartype)
180     STOP 'in S/R ctrl_unpack'
181     endif
182     read(cunit) filej
183     read(cunit) filei
184 heimbach 1.13 #endif /* ALLOW_ADMTLM */
185 heimbach 1.2 do k = 1, Nr
186 heimbach 1.9 irectrue = (irec-1)*nr + k
187 heimbach 1.10 if ( doZscaleUnpack ) then
188 heimbach 1.16 delZnorm = (delR(1)/delR(k))**delZexp
189 heimbach 1.10 else
190     delZnorm = 1. _d 0
191     endif
192 heimbach 1.2 cbuffindex = nwetglobal(k)
193     if ( cbuffindex .gt. 0 ) then
194 heimbach 1.13 #ifndef ALLOW_ADMTLM
195 heimbach 1.2 read(cunit) filencbuffindex
196     if (filencbuffindex .NE. cbuffindex) then
197     print *, 'WARNING: wrong cbuffindex ',
198     & filencbuffindex, cbuffindex
199     STOP 'in S/R ctrl_unpack'
200     endif
201     read(cunit) filek
202     if (filek .NE. k) then
203     print *, 'WARNING: wrong k ',
204     & filek, k
205     STOP 'in S/R ctrl_unpack'
206     endif
207 heimbach 1.15 cph#endif /* ALLOW_ADMTLM */
208     read(cunit) (cbuff(ii), ii=1,cbuffindex)
209 heimbach 1.13 #endif /* ALLOW_ADMTLM */
210 heimbach 1.2 endif
211 heimbach 1.13 c
212 heimbach 1.2 cbuffindex = 0
213     do jp = 1,nPy
214     do bj = jtlo,jthi
215     do j = jmin,jmax
216     do ip = 1,nPx
217     do bi = itlo,ithi
218     do i = imin,imax
219     if ( globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
220     cbuffindex = cbuffindex + 1
221     globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
222 heimbach 1.9 cph(
223     globfldtmp2(i,bi,ip,j,bj,jp) = cbuff(cbuffindex)
224     cph)
225 heimbach 1.13 #ifdef ALLOW_ADMTLM
226     nveccount = nveccount + 1
227 heimbach 1.14 globfld3d(i,bi,ip,j,bj,jp,k) =
228     & phtmpadmtlm(nveccount)
229     cph(
230     globfldtmp2(i,bi,ip,j,bj,jp) =
231     & phtmpadmtlm(nveccount)
232     cph)
233 heimbach 1.13 #endif
234 heimbach 1.2 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
235 heimbach 1.9 if ( lxxadxx ) then
236 heimbach 1.10 globfld3d(i,bi,ip,j,bj,jp,k) = delZnorm
237     & * globfld3d(i,bi,ip,j,bj,jp,k)
238 heimbach 1.9 # ifdef CTRL_UNPACK_PRECISE
239 heimbach 1.10 & / sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
240 heimbach 1.9 # else
241 heimbach 1.10 & / sqrt(weightfld(k,bi,bj))
242 heimbach 1.9 # endif
243     else
244 heimbach 1.10 globfld3d(i,bi,ip,j,bj,jp,k) = delZnorm
245     & * globfld3d(i,bi,ip,j,bj,jp,k)
246 heimbach 1.3 # ifdef CTRL_UNPACK_PRECISE
247 heimbach 1.9 & * sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
248 heimbach 1.3 # else
249 heimbach 1.9 & * sqrt(weightfld(k,bi,bj))
250 heimbach 1.3 # endif
251 heimbach 1.9 endif
252 heimbach 1.3 #endif /* ALLOW_NONDIMENSIONAL_CONTROL_IO */
253 heimbach 1.2 else
254     globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
255     endif
256 heimbach 1.9 cph(
257     globfldtmp3(i,bi,ip,j,bj,jp) =
258     & globfld3d(i,bi,ip,j,bj,jp,k)
259     cph)
260 heimbach 1.2 enddo
261     enddo
262     enddo
263     enddo
264     enddo
265     enddo
266     c
267 heimbach 1.9 if ( doPackDiag ) then
268     write(cunit2,rec=irectrue) globfldtmp2
269     write(cunit3,rec=irectrue) globfldtmp3
270     endif
271     c
272 heimbach 1.2 enddo
273    
274     call MDSWRITEFIELD_3D_GL( fname, ctrlprec, 'RL',
275     & Nr, globfld3d,
276     & irec, optimcycle, mythid)
277    
278     enddo
279    
280 heimbach 1.9 if ( doPackDiag ) then
281     close ( cunit2 )
282     close ( cunit3 )
283     endif
284    
285 heimbach 1.2 _END_MASTER( mythid )
286    
287 heimbach 1.17 #endif
288    
289 heimbach 1.2 return
290     end
291    

  ViewVC Help
Powered by ViewVC 1.1.22