/[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.7 - (hide annotations) (download)
Fri May 28 16:04:42 2004 UTC (19 years, 11 months 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.6: +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_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     c == external ==
77    
78     integer ilnblnk
79     external ilnblnk
80    
81     cc == end of interface ==
82    
83     jtlo = 1
84     jthi = nsy
85     itlo = 1
86     ithi = nsx
87     jmin = 1
88     jmax = sny
89     imin = 1
90     imax = snx
91    
92     c Initialise temporary file
93     do k = 1,nr
94     do jp = 1,nPy
95     do bj = jtlo,jthi
96     do j = jmin,jmax
97     do ip = 1,nPx
98     do bi = itlo,ithi
99     do i = imin,imax
100     globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
101     globmsk (i,bi,ip,j,bj,jp,k) = 0. _d 0
102     enddo
103     enddo
104     enddo
105     enddo
106     enddo
107     enddo
108     enddo
109    
110     #ifndef ALLOW_ECCO_OPTIMIZATION
111     optimcycle = 0
112     #endif
113    
114     c-- Only the master thread will do I/O.
115     _BEGIN_MASTER( mythid )
116    
117 heimbach 1.3 #ifdef CTRL_UNPACK_PRECISE
118     il=ilnblnk( weighttype)
119     write(weightname(1:80),'(80a)') ' '
120     write(weightname(1:80),'(a)') weighttype(1:il)
121    
122     call MDSREADFIELD_3D_GL(
123     & weightname, ctrlprec, 'RL',
124     & Nr, weightfld3d, 1, mythid)
125     #endif
126    
127 heimbach 1.2 call MDSREADFIELD_3D_GL(
128     & masktype, ctrlprec, 'RL',
129     & Nr, globmsk, 1, mythid)
130    
131     do irec = 1, ncvarrecs(ivartype)
132     read(cunit) filencvarindex(ivartype)
133     if (filencvarindex(ivartype) .NE. ncvarindex(ivartype))
134     & then
135     print *, 'ctrl_set_unpack_xyz:WARNING: wrong ncvarindex ',
136     & filencvarindex(ivartype), ncvarindex(ivartype)
137     STOP 'in S/R ctrl_unpack'
138     endif
139     read(cunit) filej
140     read(cunit) filei
141     do k = 1, Nr
142     cbuffindex = nwetglobal(k)
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. k) then
152     print *, 'WARNING: wrong k ',
153     & filek, k
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,k) .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 heimbach 1.3 # ifdef CTRL_UNPACK_PRECISE
172     & sqrt(weightfld3d(i,bi,ip,j,bj,jp,k))
173     # else
174 heimbach 1.2 & sqrt(weightfld(k,bi,bj))
175 heimbach 1.3 # endif
176     #endif /* ALLOW_NONDIMENSIONAL_CONTROL_IO */
177 heimbach 1.2 else
178     globfld3d(i,bi,ip,j,bj,jp,k) = 0. _d 0
179     endif
180     enddo
181     enddo
182     enddo
183     enddo
184     enddo
185     enddo
186     c
187     enddo
188    
189     call MDSWRITEFIELD_3D_GL( fname, ctrlprec, 'RL',
190     & Nr, globfld3d,
191     & irec, optimcycle, mythid)
192    
193     enddo
194    
195     _END_MASTER( mythid )
196    
197     return
198     end
199    

  ViewVC Help
Powered by ViewVC 1.1.22