/[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.4 - (show annotations) (download)
Thu Oct 23 04:41:40 2003 UTC (20 years, 7 months ago) by edhill
Branch: MAIN
CVS Tags: checkpoint51o_pre, checkpoint51n_post, checkpoint51n_pre, checkpoint51o_post, checkpoint51p_post
Branch point for: checkpoint51n_branch
Changes since 1.3: +4 -0 lines
 o added the [#include "AD_CONFIG.h"] statement to all files that need
   it for adjoint/tl #defines
 o re-worked the build logic in genmake2 to support AD_CONFIG.h
 o removed tools/genmake since it no longer works

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

  ViewVC Help
Powered by ViewVC 1.1.22