/[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.1.2.3 - (show annotations) (download)
Thu Apr 4 10:24:47 2002 UTC (22 years, 2 months ago) by heimbach
Branch: ecco-branch
CVS Tags: ecco_c44_e22, ecco_c44_e23, ecco_c44_e21
Changes since 1.1.2.2: +17 -5 lines
o modified to enable ctrl field swapping
o bug fix for global sum of ncvarlength in ctrl_init
o no more call to ctrl_unpack from ctrl_init
o no more write of ctrl vector in ctrl_pack
  however, init. of control vector from ctrl_unpack
o various nug fixes & consistent nobcs handling in
  ctrl_pack/unpack routines.

1
2 #include "CTRL_CPPOPTIONS.h"
3
4
5 subroutine ctrl_set_unpack_yz(
6 & cunit, ivartype, fname, masktype,
7 & weightfld, nwettile, mythid)
8
9 c ==================================================================
10 c SUBROUTINE ctrl_set_unpack_yz
11 c ==================================================================
12 c
13 c o Unpack the control vector such that the land points are filled
14 c in.
15 c
16 c ==================================================================
17
18 implicit none
19
20 c == global variables ==
21
22 #include "EEPARAMS.h"
23 #include "SIZE.h"
24 #include "PARAMS.h"
25 #include "GRID.h"
26
27 #include "cal.h"
28 #include "ecco.h"
29 #include "ctrl.h"
30 #include "cost.h"
31
32 #ifdef ALLOW_ECCO_OPTIMIZATION
33 #include "optim.h"
34 #endif
35
36 c == routine arguments ==
37
38 integer cunit
39 integer ivartype
40 character*( 80) fname
41 character* (9) masktype
42 _RL weightfld( nr,nobcs )
43 integer nwettile(nsx,nsy,nr,nobcs)
44 integer mythid
45
46 c == local variables ==
47
48 #ifndef ALLOW_ECCO_OPTIMIZATION
49 integer optimcycle
50 #endif
51
52 integer bi,bj
53 integer ip,jp
54 integer i,j,k
55 integer ii
56 integer il
57 integer irec,iobcs
58 integer itlo,ithi
59 integer jtlo,jthi
60 integer jmin,jmax
61 integer imin,imax
62
63 integer cbuffindex
64
65 _RL cbuff ( nsx*npx*sny*nsy*npy )
66 _RL globmskyz( nsx,npx,sny,nsy,npy,nr )
67 _RL globfldyz( nsx,npx,sny,nsy,npy,nr )
68
69 integer filenvartype
70 integer filenvarlength
71 character*(10) fileExpId
72 integer fileOptimCycle
73 integer filencbuffindex
74 _RL fileDummy
75 integer fileIg
76 integer fileJg
77 integer fileI
78 integer fileJ
79 integer filensx
80 integer filensy
81 integer filek
82 integer filencvarindex(maxcvars)
83 integer filencvarrecs(maxcvars)
84 integer filencvarxmax(maxcvars)
85 integer filencvarymax(maxcvars)
86 integer filencvarnrmax(maxcvars)
87 character*( 1) filencvargrd(maxcvars)
88 cgg(
89 integer igg
90 _RL gg
91 cgg)
92
93 c == external ==
94
95 integer ilnblnk
96 external ilnblnk
97
98 cc == end of interface ==
99
100 jtlo = 1
101 jthi = nsy
102 itlo = 1
103 ithi = nsx
104 jmin = 1
105 jmax = sny
106 imin = 1
107 imax = snx
108
109 c Initialise temporary file
110 do k = 1,nr
111 do jp = 1,nPy
112 do bj = jtlo,jthi
113 do j = jmin,jmax
114 do ip = 1,nPx
115 do bi = itlo,ithi
116 globfldyz(bi,ip,j,bj,jp,k) = 0. _d 0
117 globmskyz(bi,ip,j,bj,jp,k) = 0. _d 0
118 enddo
119 enddo
120 enddo
121 enddo
122 enddo
123 enddo
124
125 #ifndef ALLOW_ECCO_OPTIMIZATION
126 optimcycle = 0
127 #endif
128
129 c-- Only the master thread will do I/O.
130 _BEGIN_MASTER( mythid )
131
132 do irec = 1, ncvarrecs(ivartype)
133 cgg do iobcs = 1, nobcs
134 cgg Iobcs has already been included in the calculation
135 cgg of ncvarrecs.
136 cgg And now back-calculate what iobcs should be.
137 gg = (irec-1)/nobcs
138 igg = int(gg)
139 iobcs = irec - igg*nobcs
140
141 call MDSREADFIELD_YZ_GL(
142 & masktype, ctrlprec, 'RL',
143 & Nr, globmskyz, iobcs, mythid)
144
145 read(cunit) filencvarindex(ivartype)
146 if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
147 & then
148 print *, 'ctrl_set_unpack_yz:WARNING: wrong ncvarindex ',
149 & filencvarindex(ivartype), ncvarindex(ivartype)
150 STOP 'in S/R ctrl_unpack'
151 endif
152 read(cunit) filej
153 read(cunit) filei
154 do k = 1, Nr
155 cbuffindex = nwettile(1,1,k,iobcs)
156 if ( cbuffindex .gt. 0 ) then
157 read(cunit) filencbuffindex
158 if (filencbuffindex .NE. cbuffindex) then
159 print *, 'WARNING: wrong cbuffindex ',
160 & filencbuffindex, cbuffindex
161 STOP 'in S/R ctrl_unpack'
162 endif
163 read(cunit) filek
164 if (filek .NE. k) then
165 print *, 'WARNING: wrong k ',
166 & filek, k
167 STOP 'in S/R ctrl_unpack'
168 endif
169 read(cunit) (cbuff(ii), ii=1,cbuffindex)
170 endif
171 cbuffindex = 0
172 do jp = 1,nPy
173 do bj = jtlo,jthi
174 do j = jmin,jmax
175 do ip = 1,nPx
176 do bi = itlo,ithi
177 if ( globmskyz(bi,ip,j,bj,jp,k) .ne. 0. ) then
178 cbuffindex = cbuffindex + 1
179 globfldyz(bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
180 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
181 globfldyz(bi,ip,j,bj,jp,k) =
182 & globfldyz(bi,ip,j,bj,jp,k)/
183 & sqrt(weightfld(k,iobcs))
184 #endif
185 else
186 globfldyz(bi,ip,j,bj,jp,k) = 0. _d 0
187 endif
188 enddo
189 enddo
190 enddo
191 enddo
192 enddo
193 c
194 enddo
195
196 call MDSWRITEFIELD_YZ_GL( fname, ctrlprec, 'RL',
197 & Nr, globfldyz, irec,
198 & optimcycle, mythid)
199 cgg & Nr, globfldyz, (irec-1)*nobcs+iobcs,
200 cgg & optimcycle, mythid)
201
202 c -- end of iobcs loop -- This loop has been removed.
203 cgg enddo
204 c -- end of irec loop --
205 enddo
206
207 _END_MASTER( mythid )
208
209 return
210 end
211

  ViewVC Help
Powered by ViewVC 1.1.22