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

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

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


Revision 1.8 - (hide annotations) (download)
Fri May 28 16:04:42 2004 UTC (21 years, 1 month ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint54d_post, checkpoint54e_post, checkpoint55, checkpoint54, checkpoint54f_post, checkpoint55i_post, checkpoint55c_post, checkpoint53d_post, checkpoint54b_post, checkpoint55g_post, checkpoint55d_post, checkpoint54a_pre, checkpoint55d_pre, checkpoint55j_post, checkpoint54a_post, checkpoint55h_post, checkpoint55b_post, checkpoint55f_post, checkpoint53g_post, checkpoint53f_post, checkpoint55a_post, checkpoint55e_post, checkpoint54c_post
Changes since 1.7: +0 -20 lines
Use ctrl_pack/unpack as standalone to map back and forth
between xx_/adxx_ and vector
(useful when analysing wetpoint gradient- and control-VECTOR)
Needs modified the_model_main.F

1 heimbach 1.2
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 heimbach 1.3 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 heimbach 1.2 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 heimbach 1.3 integer irec,nrec_nl
59 heimbach 1.2 integer itlo,ithi
60     integer jtlo,jthi
61     integer jmin,jmax
62     integer imin,imax
63    
64     integer cbuffindex
65    
66 heimbach 1.6 real*4 cbuff ( snx*nsx*npx*sny*nsy*npy )
67 heimbach 1.2 _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     c == external ==
75    
76     integer ilnblnk
77     external ilnblnk
78    
79     c == end of interface ==
80    
81     jtlo = 1
82     jthi = nsy
83     itlo = 1
84     ithi = nsx
85     jmin = 1
86     jmax = sny
87     imin = 1
88     imax = snx
89    
90     c Initialise temporary file
91     do k = 1,nr
92     do jp = 1,nPy
93     do bj = jtlo,jthi
94     do j = jmin,jmax
95     do ip = 1,nPx
96     do bi = itlo,ithi
97     do i = imin,imax
98     globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
99     globmsk (i,bi,ip,j,bj,jp,k) = 0. _d 0
100     enddo
101     enddo
102     enddo
103     enddo
104     enddo
105     enddo
106     enddo
107    
108     #ifndef ALLOW_ECCO_OPTIMIZATION
109     optimcycle = 0
110     #endif
111    
112     c-- Only the master thread will do I/O.
113     _BEGIN_MASTER( mythid )
114    
115     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
116     il=ilnblnk( weighttype)
117     write(weightname(1:80),'(80a)') ' '
118     write(weightname(1:80),'(a)') weighttype(1:il)
119     call MDSREADFIELD_2D_GL(
120     & weightname, ctrlprec, 'RL',
121     & 1, globfld2d, 1, mythid)
122     #endif
123    
124     call MDSREADFIELD_3D_GL(
125     & masktype, ctrlprec, 'RL',
126     & Nr, globmsk, 1, mythid)
127    
128 heimbach 1.3 nrec_nl=int(ncvarrecs(ivartype)/Nr)
129     do irec = 1, nrec_nl
130 heimbach 1.7 print *, 'ph-pack nrec_nl = ', irec, nrec_nl, ivartype,
131     & ncvarrecs(ivartype)
132 heimbach 1.3 do k = 1,Nr
133     read(cunit) filencvarindex(ivartype)
134     if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
135     & then
136     print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
137     & filencvarindex(ivartype), ncvarindex(ivartype)
138     STOP 'in S/R ctrl_unpack'
139     endif
140     read(cunit) filej
141     read(cunit) filei
142     cbuffindex = nwetglobal(1)
143     if ( cbuffindex .gt. 0 ) then
144     read(cunit) filencbuffindex
145     if (filencbuffindex .NE. cbuffindex) then
146     print *, 'WARNING: wrong cbuffindex ',
147     & filencbuffindex, cbuffindex
148     STOP 'in S/R ctrl_unpack'
149     endif
150     read(cunit) filek
151     if (filek .NE. 1) then
152     print *, 'WARNING: wrong k ',
153     & filek, 1
154     STOP 'in S/R ctrl_unpack'
155     endif
156     read(cunit) (cbuff(ii), ii=1,cbuffindex)
157     endif
158     cbuffindex = 0
159     do jp = 1,nPy
160     do bj = jtlo,jthi
161     do j = jmin,jmax
162     do ip = 1,nPx
163     do bi = itlo,ithi
164     do i = imin,imax
165     if ( globmsk(i,bi,ip,j,bj,jp,1) .ne. 0. ) then
166     cbuffindex = cbuffindex + 1
167     globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
168     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
169     globfld3d(i,bi,ip,j,bj,jp,k) =
170     & globfld3d(i,bi,ip,j,bj,jp,k)/
171     & sqrt(globfld2d(i,bi,ip,j,bj,jp))
172     #endif
173     else
174     globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
175     endif
176     enddo
177     enddo
178     enddo
179     enddo
180     enddo
181     enddo
182     c
183     enddo
184    
185     call MDSWRITEFIELD_3D_GL( fname, ctrlprec, 'RL',
186     & NR, globfld3d,
187     & irec, optimcycle, mythid)
188    
189     enddo
190    
191     do irec = nrec_nl*Nr+1,ncvarrecs(ivartype)
192 heimbach 1.7 print *, 'ph-pack nrec_nl+irec ', irec, nrec_nl, ivartype,
193     & ncvarrecs(ivartype)
194    
195 heimbach 1.2 read(cunit) filencvarindex(ivartype)
196     if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
197     & then
198     print *, 'ctrl_set_unpack_xy:WARNING: wrong ncvarindex ',
199     & filencvarindex(ivartype), ncvarindex(ivartype)
200     STOP 'in S/R ctrl_unpack'
201     endif
202     read(cunit) filej
203     read(cunit) filei
204     do k = 1,1
205     cbuffindex = nwetglobal(k)
206     if ( cbuffindex .gt. 0 ) then
207     read(cunit) filencbuffindex
208     if (filencbuffindex .NE. cbuffindex) then
209     print *, 'WARNING: wrong cbuffindex ',
210     & filencbuffindex, cbuffindex
211     STOP 'in S/R ctrl_unpack'
212     endif
213     read(cunit) filek
214     if (filek .NE. k) then
215     print *, 'WARNING: wrong k ',
216     & filek, k
217     STOP 'in S/R ctrl_unpack'
218     endif
219     read(cunit) (cbuff(ii), ii=1,cbuffindex)
220     endif
221     cbuffindex = 0
222     do jp = 1,nPy
223     do bj = jtlo,jthi
224     do j = jmin,jmax
225     do ip = 1,nPx
226     do bi = itlo,ithi
227     do i = imin,imax
228     if ( globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
229     cbuffindex = cbuffindex + 1
230     globfld3d(i,bi,ip,j,bj,jp,k) = cbuff(cbuffindex)
231     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
232     globfld3d(i,bi,ip,j,bj,jp,k) =
233     & globfld3d(i,bi,ip,j,bj,jp,k)/
234     & sqrt(globfld2d(i,bi,ip,j,bj,jp))
235     #endif
236     else
237     globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
238     endif
239     enddo
240     enddo
241     enddo
242     enddo
243     enddo
244     enddo
245     c
246     enddo
247    
248     call MDSWRITEFIELD_2D_GL( fname, ctrlprec, 'RL',
249     & 1, globfld3d(1,1,1,1,1,1,1),
250     & irec, optimcycle, mythid)
251    
252     enddo
253    
254     _END_MASTER( mythid )
255    
256     return
257     end
258    

  ViewVC Help
Powered by ViewVC 1.1.22