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

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

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


Revision 1.5 - (hide annotations) (download)
Thu Oct 30 19:09:06 2003 UTC (20 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint51t_post, checkpoint51s_post, checkpoint51q_post, checkpoint51r_post
Branch point for: branch-nonh
Changes since 1.4: +2 -3 lines
ctrl package totally restructured
o pack/unpack now optional and decoupled from
  xx_/adxx_ I/O
o ctrl_pack/unpack cleaned
  (new routines ctrl_init_ctrlvar.F, pkg/ctrl/ctrl_init_wet.F)
o confined inclusion of AD_CONFIG.h to where necessary.

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

  ViewVC Help
Powered by ViewVC 1.1.22