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

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

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


Revision 1.8 - (show annotations) (download)
Tue Nov 16 05:42:12 2004 UTC (19 years, 6 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint57b_post, checkpoint56b_post, checkpoint57, checkpoint56, checkpoint57a_post, checkpoint56a_post, checkpoint56c_post, checkpoint57a_pre
Changes since 1.7: +0 -11 lines
More on dsvd vs. MITgcm interfacing
o handling of g_, ad, via admtlm_vector (mds...vector)
o use ctrl_pack/unpack for admtlm_vector I/O
o use optimcycle for dsvd iteration
o make sure norm is w.r.t. derived quantities

1
2 #include "CTRL_CPPOPTIONS.h"
3
4 subroutine ctrl_set_pack_xyz(
5 & cunit, ivartype, fname, masktype, weighttype,
6 & 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 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 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 character* (5) masktype
40 character*( 80) weighttype
41 _RL weightfld( nr,nsx,nsy )
42 logical lxxadxx
43 integer mythid
44
45 c == local variables ==
46
47 integer bi,bj
48 integer ip,jp
49 integer i,j,k
50 integer ii
51 integer il
52 integer irec
53 integer itlo,ithi
54 integer jtlo,jthi
55 integer jmin,jmax
56 integer imin,imax
57
58 integer cbuffindex
59
60 real*4 cbuff ( snx*nsx*npx*sny*nsy*npy )
61 _RL globmsk ( snx,nsx,npx,sny,nsy,npy,nr )
62 _RL globfld3d( snx,nsx,npx,sny,nsy,npy,nr )
63 #ifdef CTRL_PACK_PRECISE
64 _RL weightfld3d( snx,nsx,npx,sny,nsy,npy,nr )
65 #endif
66
67 character*(80) weightname
68
69 c == external ==
70
71 integer ilnblnk
72 external ilnblnk
73
74 c == end of interface ==
75
76 jtlo = 1
77 jthi = nsy
78 itlo = 1
79 ithi = nsx
80 jmin = 1
81 jmax = sny
82 imin = 1
83 imax = snx
84
85 c Initialise temporary file
86 do k = 1,nr
87 do jp = 1,nPy
88 do bj = jtlo,jthi
89 do j = jmin,jmax
90 do ip = 1,nPx
91 do bi = itlo,ithi
92 do i = imin,imax
93 globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
94 globmsk (i,bi,ip,j,bj,jp,k) = 0. _d 0
95 enddo
96 enddo
97 enddo
98 enddo
99 enddo
100 enddo
101 enddo
102
103 c-- Only the master thread will do I/O.
104 _BEGIN_MASTER( mythid )
105
106 #ifdef CTRL_PACK_PRECISE
107 il=ilnblnk( weighttype)
108 write(weightname(1:80),'(80a)') ' '
109 write(weightname(1:80),'(a)') weighttype(1:il)
110
111 call MDSREADFIELD_3D_GL(
112 & weightname, ctrlprec, 'RL',
113 & Nr, weightfld3d, 1, mythid)
114 #endif
115
116 call MDSREADFIELD_3D_GL(
117 & masktype, ctrlprec, 'RL',
118 & Nr, globmsk, 1, mythid)
119
120 do irec = 1, ncvarrecs(ivartype)
121
122 call MDSREADFIELD_3D_GL( fname, ctrlprec, 'RL',
123 & Nr, globfld3d, irec, mythid)
124
125 write(cunit) ncvarindex(ivartype)
126 write(cunit) 1
127 write(cunit) 1
128 do k = 1, nr
129 cbuffindex = 0
130 do jp = 1,nPy
131 do bj = jtlo,jthi
132 do j = jmin,jmax
133 do ip = 1,nPx
134 do bi = itlo,ithi
135 do i = imin,imax
136 if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
137 cbuffindex = cbuffindex + 1
138 #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
139 if (lxxadxx) then
140 cbuff(cbuffindex) =
141 & globfld3d(i,bi,ip,j,bj,jp,k) *
142 # ifdef CTRL_PACK_PRECISE
143 & sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
144 # else
145 & sqrt(weightfld(k,bi,bj))
146 # endif
147 else
148 cbuff(cbuffindex) =
149 & globfld3d(i,bi,ip,j,bj,jp,k) /
150 # ifdef CTRL_PACK_PRECISE
151 & sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
152 # else
153 & sqrt(weightfld(k,bi,bj))
154 # endif
155 endif
156 #else /* ALLOW_NONDIMENSIONAL_CONTROL_IO undef */
157 cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
158 #endif /* ALLOW_NONDIMENSIONAL_CONTROL_IO */
159 endif
160 enddo
161 enddo
162 enddo
163 enddo
164 enddo
165 enddo
166 c --> check cbuffindex.
167 if ( cbuffindex .gt. 0) then
168 write(cunit) cbuffindex
169 write(cunit) k
170 write(cunit) (cbuff(ii), ii=1,cbuffindex)
171 endif
172 enddo
173 c
174 c -- end of irec loop --
175 enddo
176
177 _END_MASTER( mythid )
178
179 return
180 end
181

  ViewVC Help
Powered by ViewVC 1.1.22