/[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.6 - (hide annotations) (download)
Thu Nov 6 22:05:08 2003 UTC (20 years, 7 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint52l_pre, hrcube4, hrcube5, checkpoint52d_pre, checkpoint52j_pre, checkpoint52l_post, checkpoint52k_post, checkpoint53, checkpoint52, checkpoint52f_post, checkpoint52i_pre, hrcube_1, hrcube_2, hrcube_3, checkpoint52e_pre, checkpoint52e_post, checkpoint52b_pre, checkpoint52m_post, checkpoint52b_post, checkpoint52c_post, checkpoint52f_pre, checkpoint53c_post, checkpoint53a_post, checkpoint52d_post, checkpoint52a_pre, checkpoint52i_post, checkpoint52h_pre, checkpoint52j_post, branch-netcdf, checkpoint52n_post, checkpoint53b_pre, checkpoint53b_post, checkpoint52a_post, ecco_c52_e35, checkpoint53d_pre, checkpoint51u_post
Branch point for: netcdf-sm0
Changes since 1.5: +1 -6 lines
o merging from ecco-branch
o cleaned some cross-dependencies and updated CPP options

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

  ViewVC Help
Powered by ViewVC 1.1.22