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

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

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


Revision 1.6 - (show annotations) (download)
Thu Nov 6 22:05:08 2003 UTC (20 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: hrcube4, checkpoint52d_pre, checkpoint52j_pre, checkpoint52k_post, checkpoint52, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_pre, checkpoint52e_post, checkpoint52b_pre, checkpoint52b_post, checkpoint52c_post, checkpoint52f_pre, checkpoint52d_post, checkpoint52a_pre, checkpoint52i_post, checkpoint52h_pre, checkpoint52j_post, branch-netcdf, checkpoint52a_post, ecco_c52_e35, checkpoint51u_post
Branch point for: netcdf-sm0
Changes since 1.5: +1 -6 lines
o merging from ecco-branch
o cleaned some cross-dependencies and updated CPP options

1
2 #include "CTRL_CPPOPTIONS.h"
3
4 subroutine ctrl_set_unpack_xy(
5 & cunit, ivartype, fname, masktype, weighttype,
6 & nwetglobal, mythid)
7
8 c ==================================================================
9 c SUBROUTINE ctrl_set_unpack_xy
10 c ==================================================================
11 c
12 c o Unpack the control vector such that the land points are filled
13 c in.
14 c
15 c changed: heimbach@mit.edu 17-Jun-2003
16 c merged Armin's changes to replace write of
17 c nr * globfld2d by 1 * globfld3d
18 c (ad hoc fix to speed up global I/O)
19 c
20 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
33 #ifdef ALLOW_ECCO_OPTIMIZATION
34 #include "optim.h"
35 #endif
36
37 c == routine arguments ==
38
39 integer cunit
40 integer ivartype
41 character*( 80) fname
42 character*( 5) masktype
43 character*( 80) weighttype
44 integer nwetglobal(nr)
45 integer mythid
46
47 c == local variables ==
48
49 #ifndef ALLOW_ECCO_OPTIMIZATION
50 integer optimcycle
51 #endif
52
53 integer bi,bj
54 integer ip,jp
55 integer i,j,k
56 integer ii
57 integer il
58 integer irec,nrec_nl
59 integer itlo,ithi
60 integer jtlo,jthi
61 integer jmin,jmax
62 integer imin,imax
63
64 integer cbuffindex
65
66 real*4 cbuff ( snx*nsx*npx*sny*nsy*npy )
67 _RL globmsk ( snx,nsx,npx,sny,nsy,npy,nr )
68 _RL globfld3d( snx,nsx,npx,sny,nsy,npy,nr )
69 _RL globfld2d( snx,nsx,npx,sny,nsy,npy )
70
71 character*(128) cfile
72 character*( 80) weightname
73
74 integer filenvartype
75 integer filenvarlength
76 character*(10) fileExpId
77 integer fileOptimCycle
78 integer filencbuffindex
79 _RL fileDummy
80 integer fileIg
81 integer fileJg
82 integer fileI
83 integer fileJ
84 integer filensx
85 integer filensy
86 integer filek
87 integer filencvarindex(maxcvars)
88 integer filencvarrecs(maxcvars)
89 integer filencvarxmax(maxcvars)
90 integer filencvarymax(maxcvars)
91 integer filencvarnrmax(maxcvars)
92 character*( 1) filencvargrd(maxcvars)
93
94 c == external ==
95
96 integer ilnblnk
97 external ilnblnk
98
99 c == end of interface ==
100
101 jtlo = 1
102 jthi = nsy
103 itlo = 1
104 ithi = nsx
105 jmin = 1
106 jmax = sny
107 imin = 1
108 imax = snx
109
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 globmsk (i,bi,ip,j,bj,jp,k) = 0. _d 0
120 enddo
121 enddo
122 enddo
123 enddo
124 enddo
125 enddo
126 enddo
127
128 #ifndef ALLOW_ECCO_OPTIMIZATION
129 optimcycle = 0
130 #endif
131
132 c-- Only the master thread will do I/O.
133 _BEGIN_MASTER( mythid )
134
135 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
136 il=ilnblnk( weighttype)
137 write(weightname(1:80),'(80a)') ' '
138 write(weightname(1:80),'(a)') weighttype(1:il)
139 call MDSREADFIELD_2D_GL(
140 & weightname, ctrlprec, 'RL',
141 & 1, globfld2d, 1, mythid)
142 #endif
143
144 call MDSREADFIELD_3D_GL(
145 & masktype, ctrlprec, 'RL',
146 & Nr, globmsk, 1, mythid)
147
148 nrec_nl=int(ncvarrecs(ivartype)/Nr)
149 do irec = 1, nrec_nl
150 do k = 1,Nr
151 read(cunit) filencvarindex(ivartype)
152 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
153 & then
154 print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
155 & filencvarindex(ivartype), ncvarindex(ivartype)
156 STOP 'in S/R ctrl_unpack'
157 endif
158 read(cunit) filej
159 read(cunit) filei
160 cbuffindex = nwetglobal(1)
161 if ( cbuffindex .gt. 0 ) then
162 read(cunit) filencbuffindex
163 if (filencbuffindex .NE. cbuffindex) then
164 print *, 'WARNING: wrong cbuffindex ',
165 & filencbuffindex, cbuffindex
166 STOP 'in S/R ctrl_unpack'
167 endif
168 read(cunit) filek
169 if (filek .NE. 1) then
170 print *, 'WARNING: wrong k ',
171 & filek, 1
172 STOP 'in S/R ctrl_unpack'
173 endif
174 read(cunit) (cbuff(ii), ii=1,cbuffindex)
175 endif
176 cbuffindex = 0
177 do jp = 1,nPy
178 do bj = jtlo,jthi
179 do j = jmin,jmax
180 do ip = 1,nPx
181 do bi = itlo,ithi
182 do i = imin,imax
183 if ( globmsk(i,bi,ip,j,bj,jp,1) .ne. 0. ) then
184 cbuffindex = cbuffindex + 1
185 globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
186 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
187 globfld3d(i,bi,ip,j,bj,jp,k) =
188 & globfld3d(i,bi,ip,j,bj,jp,k)/
189 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
190 #endif
191 else
192 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
193 endif
194 enddo
195 enddo
196 enddo
197 enddo
198 enddo
199 enddo
200 c
201 enddo
202
203 call MDSWRITEFIELD_3D_GL( fname, ctrlprec, 'RL',
204 & NR, globfld3d,
205 & irec, optimcycle, mythid)
206
207 enddo
208
209 do irec = nrec_nl*Nr+1,ncvarrecs(ivartype)
210 read(cunit) filencvarindex(ivartype)
211 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
212 & then
213 print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
214 & filencvarindex(ivartype), ncvarindex(ivartype)
215 STOP 'in S/R ctrl_unpack'
216 endif
217 read(cunit) filej
218 read(cunit) filei
219 do k = 1,1
220 cbuffindex = nwetglobal(k)
221 if ( cbuffindex .gt. 0 ) then
222 read(cunit) filencbuffindex
223 if (filencbuffindex .NE. cbuffindex) then
224 print *, 'WARNING: wrong cbuffindex ',
225 & filencbuffindex, cbuffindex
226 STOP 'in S/R ctrl_unpack'
227 endif
228 read(cunit) filek
229 if (filek .NE. k) then
230 print *, 'WARNING: wrong k ',
231 & filek, k
232 STOP 'in S/R ctrl_unpack'
233 endif
234 read(cunit) (cbuff(ii), ii=1,cbuffindex)
235 endif
236 cbuffindex = 0
237 do jp = 1,nPy
238 do bj = jtlo,jthi
239 do j = jmin,jmax
240 do ip = 1,nPx
241 do bi = itlo,ithi
242 do i = imin,imax
243 if ( globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
244 cbuffindex = cbuffindex + 1
245 globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
246 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
247 globfld3d(i,bi,ip,j,bj,jp,k) =
248 & globfld3d(i,bi,ip,j,bj,jp,k)/
249 & sqrt(globfld2d(i,bi,ip,j,bj,jp))
250 #endif
251 else
252 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
253 endif
254 enddo
255 enddo
256 enddo
257 enddo
258 enddo
259 enddo
260 c
261 enddo
262
263 call MDSWRITEFIELD_2D_GL( fname, ctrlprec, 'RL',
264 & 1, globfld3d(1,1,1,1,1,1,1),
265 & irec, optimcycle, mythid)
266
267 enddo
268
269 _END_MASTER( mythid )
270
271 return
272 end
273

  ViewVC Help
Powered by ViewVC 1.1.22