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

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

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


Revision 1.4.6.1 - (hide annotations) (download)
Tue Feb 5 20:23:58 2002 UTC (22 years, 5 months ago) by heimbach
Branch: ecco-branch
CVS Tags: ecco_c44_e17, ecco_c44_e16, ecco-branch-mod1, ecco-branch-mod2, ecco-branch-mod3, ecco-branch-mod4, ecco-branch-mod5
Changes since 1.4: +379 -1148 lines
Starting from ecco-branch, replacing packages
cost, ctrl, ecco, obcs by ECCO packages.
Will create tag ecco-branch-mod1 after this modif.

1 heimbach 1.4.6.1 C $Header: /u/gcmpack/development/heimbach/ecco_env/pkg/ctrl/ctrl_pack.F,v 1.13 2001/08/31 13:20:04 heimbach Exp $
2 heimbach 1.1
3     #include "CTRL_CPPOPTIONS.h"
4    
5    
6 heimbach 1.4.6.1 subroutine ctrl_pack(
7     I myiter,
8     I mytime,
9     I mythid
10     & )
11    
12     c ==================================================================
13     c SUBROUTINE ctrl_pack
14     c ==================================================================
15     c
16     c o Compress the control vector such that only ocean points are
17     c written to file.
18     c
19     c started: Christian Eckert eckert@mit.edu 10-Mar=2000
20     c
21     c changed: Patrick Heimbach heimbach@mit.edu 06-Jun-2000
22     c - Transferred some filename declarations
23     c from here to namelist in ctrl_init
24     c
25     c Patrick Heimbach heimbach@mit.edu 16-Jun-2000
26     c - single file name convention with or without
27     c ALLOW_ECCO_OPTIMIZATION
28     c
29     c
30     c ==================================================================
31     c SUBROUTINE ctrl_pack
32     c ==================================================================
33    
34 heimbach 1.1 implicit none
35    
36     c == global variables ==
37 heimbach 1.4.6.1
38 heimbach 1.1 #include "EEPARAMS.h"
39     #include "SIZE.h"
40     #include "PARAMS.h"
41     #include "GRID.h"
42 heimbach 1.4.6.1
43     #include "cal.h"
44     #include "ecco.h"
45 heimbach 1.1 #include "ctrl.h"
46     #include "cost.h"
47 heimbach 1.4.6.1
48     #ifdef ALLOW_ECCO_OPTIMIZATION
49 heimbach 1.2 #include "optim.h"
50 heimbach 1.4.6.1 #endif
51 heimbach 1.1
52     c == routine arguments ==
53 heimbach 1.4.6.1
54 heimbach 1.1 integer myiter
55     _RL mytime
56     integer mythid
57    
58     c == local variables ==
59    
60 heimbach 1.4.6.1 #ifndef ALLOW_ECCO_OPTIMIZATION
61     integer optimcycle
62     #endif
63    
64     integer i, j, k
65 heimbach 1.1 integer ii
66     integer il
67     integer irec
68 heimbach 1.4.6.1 integer ig,jg
69     integer ivartype
70 heimbach 1.1
71     logical doglobalread
72     logical ladinit
73 heimbach 1.4.6.1 integer cbuffindex
74 heimbach 1.1
75 heimbach 1.4.6.1 integer cunit
76 heimbach 1.1 _RL tmpvar
77    
78     character*(128) cfile
79 heimbach 1.4.6.1 character*( 80) weighttype
80    
81     character*( 80) fname_theta
82     character*( 80) fname_salt
83     character*( 80) fname_hflux
84     character*( 80) fname_sflux
85     character*( 80) fname_tauu
86     character*( 80) fname_tauv
87     character*( 80) adfname_theta
88     character*( 80) adfname_salt
89     character*( 80) adfname_hflux
90     character*( 80) adfname_sflux
91     character*( 80) adfname_tauu
92     character*( 80) adfname_tauv
93     character*( 80) fname_atemp
94     character*( 80) adfname_atemp
95     character*( 80) fname_aqh
96     character*( 80) adfname_aqh
97     character*( 80) fname_uwind
98     character*( 80) adfname_uwind
99     character*( 80) fname_vwind
100     character*( 80) adfname_vwind
101     character*( 80) fname_obcsn
102     character*( 80) adfname_obcsn
103     character*( 80) fname_obcss
104     character*( 80) adfname_obcss
105     character*( 80) fname_obcsw
106     character*( 80) adfname_obcsw
107     character*( 80) fname_obcse
108     character*( 80) adfname_obcse
109    
110     logical lxxadxx
111 heimbach 1.1
112     c == external ==
113 heimbach 1.4.6.1
114 heimbach 1.1 integer ilnblnk
115     external ilnblnk
116    
117     c == end of interface ==
118    
119 heimbach 1.4.6.1 #ifndef ALLOW_ECCO_OPTIMIZATION
120     optimcycle = 0
121     #endif
122 heimbach 1.1
123 heimbach 1.4.6.1 tmpvar = -9999. _d 0
124 heimbach 1.1
125     c-- Tiled files are used.
126     doglobalread = .false.
127    
128     c-- Initialise adjoint variables on active files.
129     ladinit = .false.
130    
131 heimbach 1.4.6.1 c-- Assign file names.
132    
133     #ifdef ALLOW_THETA0_CONTROL
134     call ctrl_set_fname(
135     & xx_theta_file, fname_theta, adfname_theta, mythid )
136     #endif
137    
138     #ifdef ALLOW_SALT0_CONTROL
139     call ctrl_set_fname(
140     I xx_salt_file, fname_salt, adfname_salt, mythid )
141     #endif
142    
143     #ifdef ALLOW_HFLUX_CONTROL
144     call ctrl_set_fname(
145     I xx_hflux_file, fname_hflux, adfname_hflux, mythid )
146     #endif
147    
148     #ifdef ALLOW_SFLUX_CONTROL
149     call ctrl_set_fname(
150     I xx_sflux_file, fname_sflux, adfname_sflux, mythid )
151     #endif
152    
153     #ifdef ALLOW_USTRESS_CONTROL
154     call ctrl_set_fname(
155     I xx_tauu_file, fname_tauu, adfname_tauu, mythid )
156     #endif
157    
158     #ifdef ALLOW_VSTRESS_CONTROL
159     call ctrl_set_fname(
160     I xx_tauv_file, fname_tauv, adfname_tauv, mythid )
161     #endif
162    
163     #ifdef ALLOW_ATEMP_CONTROL
164     call ctrl_set_fname(
165     I xx_atemp_file, fname_atemp, adfname_atemp, mythid )
166     #endif
167    
168     #ifdef ALLOW_AQH_CONTROL
169     call ctrl_set_fname(
170     I xx_aqh_file, fname_aqh, adfname_aqh, mythid )
171     #endif
172    
173     #ifdef ALLOW_UWIND_CONTROL
174     call ctrl_set_fname(
175     I xx_uwind_file, fname_uwind, adfname_uwind, mythid )
176     #endif
177    
178     #ifdef ALLOW_VWIND_CONTROL
179     call ctrl_set_fname(
180     I xx_vwind_file, fname_vwind, adfname_vwind, mythid )
181     #endif
182    
183     #ifdef ALLOW_OBCSN_CONTROL
184     call ctrl_set_fname(
185     I xx_obcsn_file, fname_obcsn, adfname_obcsn, mythid )
186     #endif
187 heimbach 1.1
188 heimbach 1.4.6.1 #ifdef ALLOW_OBCSS_CONTROL
189     call ctrl_set_fname(
190     I xx_obcss_file, fname_obcss, adfname_obcss, mythid )
191     #endif
192 heimbach 1.1
193 heimbach 1.4.6.1 #ifdef ALLOW_OBCSW_CONTROL
194     call ctrl_set_fname(
195     I xx_obcsw_file, fname_obcsw, adfname_obcsw, mythid )
196     #endif
197    
198     #ifdef ALLOW_OBCSE_CONTROL
199     call ctrl_set_fname(
200     I xx_obcse_file, fname_obcse, adfname_obcse, mythid )
201     #endif
202    
203     c
204     c-- Only the master thread will do I/O.
205     _BEGIN_MASTER( mythid )
206 heimbach 1.1
207     c >>> Write control vector <<<
208 heimbach 1.4.6.1 lxxadxx = .TRUE.
209 heimbach 1.1
210     call mdsfindunit( cunit, mythid )
211 heimbach 1.4.6.1 write(cfile(1:128),'(4a,i4.4)')
212     & ctrlname(1:9),'_',expId(1:10),'.opt',
213 heimbach 1.1 & optimcycle
214    
215     open( cunit, file = cfile,
216     & status = 'unknown',
217     & form = 'unformatted',
218     & access = 'sequential' )
219    
220     c-- Header information.
221    
222     write(cunit) nvartype
223     write(cunit) nvarlength
224     write(cunit) expId
225     write(cunit) optimCycle
226     write(cunit) tmpvar
227     write(cunit) 1
228     write(cunit) 1
229     write(cunit) 1
230     write(cunit) 1
231     write(cunit) (nWetcTile(1,1,k), k=1,nr)
232     write(cunit) (nWetsTile(1,1,k), k=1,nr)
233     write(cunit) (nWetwTile(1,1,k), k=1,nr)
234     write(cunit) (ncvarindex(i), i=1,maxcvars)
235     write(cunit) (ncvarrecs(i), i=1,maxcvars)
236     write(cunit) (nx, i=1,maxcvars)
237     write(cunit) (ny, i=1,maxcvars)
238     write(cunit) (ncvarnrmax(i), i=1,maxcvars)
239     write(cunit) (ncvargrd(i), i=1,maxcvars)
240     write(cunit)
241    
242     #ifdef ALLOW_THETA0_CONTROL
243 heimbach 1.4.6.1 ivartype = 1
244     call ctrl_set_pack_xyz(
245     & cunit, ivartype, fname_theta, "hFacC",
246     & wtheta, lxxadxx, mythid)
247 heimbach 1.1 #endif
248    
249     #ifdef ALLOW_SALT0_CONTROL
250 heimbach 1.4.6.1 ivartype = 2
251     call ctrl_set_pack_xyz(
252     & cunit, ivartype, fname_salt, "hFacC",
253     & wsalt, lxxadxx, mythid)
254     #endif
255    
256     #ifdef ALLOW_HFLUX_CONTROL
257     ivartype = 3
258     write(weighttype(1:80),'(80a)') ' '
259     write(weighttype(1:80),'(a)') "whflux"
260     call ctrl_set_pack_xy(
261     & cunit, ivartype, fname_hflux, "hFacC", weighttype,
262     & lxxadxx, mythid)
263     #endif
264    
265     #ifdef ALLOW_SFLUX_CONTROL
266     ivartype = 4
267     write(weighttype(1:80),'(80a)') ' '
268     write(weighttype(1:80),'(a)') "wsflux"
269     call ctrl_set_pack_xy(
270     & cunit, ivartype, fname_sflux, "hFacC", weighttype,
271     & lxxadxx, mythid)
272     #endif
273    
274     #ifdef ALLOW_USTRESS_CONTROL
275     ivartype = 5
276     write(weighttype(1:80),'(80a)') ' '
277     write(weighttype(1:80),'(a)') "wtauu"
278     call ctrl_set_pack_xy(
279     & cunit, ivartype, fname_tauu, "maskW", weighttype,
280     & lxxadxx, mythid)
281     #endif
282    
283     #ifdef ALLOW_VSTRESS_CONTROL
284     ivartype = 6
285     write(weighttype(1:80),'(80a)') ' '
286     write(weighttype(1:80),'(a)') "wtauv"
287     call ctrl_set_pack_xy(
288     & cunit, ivartype, fname_tauv, "maskS", weighttype,
289     & lxxadxx, mythid)
290     #endif
291    
292     #ifdef ALLOW_ATEMP_CONTROL
293     ivartype = 7
294     write(weighttype(1:80),'(80a)') ' '
295     write(weighttype(1:80),'(a)') "watemp"
296     call ctrl_set_pack_xy(
297     & cunit, ivartype, fname_atemp, "hFacC", weighttype,
298     & lxxadxx, mythid)
299     #endif
300    
301     #ifdef ALLOW_AQH_CONTROL
302     ivartype = 8
303     write(weighttype(1:80),'(80a)') ' '
304     write(weighttype(1:80),'(a)') "waqh"
305     call ctrl_set_pack_xy(
306     & cunit, ivartype, fname_aqh, "hFacC", weighttype,
307     & lxxadxx, mythid)
308     #endif
309    
310     #ifdef ALLOW_UWIND_CONTROL
311     ivartype = 9
312     write(weighttype(1:80),'(80a)') ' '
313     write(weighttype(1:80),'(a)') "wuwind"
314     call ctrl_set_pack_xy(
315     & cunit, ivartype, fname_uwind, "maskW", weighttype,
316     & lxxadxx, mythid)
317     #endif
318    
319     #ifdef ALLOW_VWIND_CONTROL
320     ivartype = 10
321     write(weighttype(1:80),'(80a)') ' '
322     write(weighttype(1:80),'(a)') "wvwind"
323     call ctrl_set_pack_xy(
324     & cunit, ivartype, fname_vwind, "maskS", weighttype,
325     & lxxadxx, mythid)
326     #endif
327    
328     #ifdef ALLOW_OBCSN_CONTROL
329     ivartype = 11
330     call ctrl_set_pack_xz(
331     & cunit, ivartype, fname_obcsn, "maskobcsn",
332     & wobcsn, lxxadxx, mythid)
333     #endif
334    
335     #ifdef ALLOW_OBCSS_CONTROL
336     ivartype = 12
337     call ctrl_set_pack_xz(
338     & cunit, ivartype, fname_obcsn, "maskobcss",
339     & wobcss, lxxadxx, mythid)
340     #endif
341    
342     #ifdef ALLOW_OBCSW_CONTROL
343     ivartype = 13
344     call ctrl_set_pack_yz(
345     & cunit, ivartype, fname_obcsw, "maskobcsw",
346     & wobcsw, lxxadxx, mythid)
347     #endif
348    
349     #ifdef ALLOW_OBCSE_CONTROL
350     ivartype = 14
351     call ctrl_set_pack_yz(
352     & cunit, ivartype, fname_obcse, "maskobcse",
353     & wobcse, lxxadxx, mythid)
354 heimbach 1.3 #endif
355 heimbach 1.1
356     close ( cunit )
357    
358     _END_MASTER( mythid )
359    
360     c >>> Write gradient vector <<<
361 heimbach 1.4.6.1 lxxadxx = .FALSE.
362 heimbach 1.1
363     call mdsfindunit( cunit, mythid )
364 heimbach 1.4.6.1 write(cfile(1:128),'(4a,i4.4)')
365     & costname(1:9),'_',expId(1:10),'.opt',
366 heimbach 1.1 & optimcycle
367    
368     open( cunit, file = cfile,
369     & status = 'unknown',
370     & form = 'unformatted',
371     & access = 'sequential' )
372    
373     c-- Header information.
374     write(cunit) nvartype
375     write(cunit) nvarlength
376     write(cunit) expId
377     write(cunit) optimCycle
378     write(cunit) fc
379     write(cunit) 1
380     write(cunit) 1
381     write(cunit) 1
382     write(cunit) 1
383     write(cunit) (nWetcTile(1,1,k), k=1,nr)
384     write(cunit) (nWetsTile(1,1,k), k=1,nr)
385     write(cunit) (nWetwTile(1,1,k), k=1,nr)
386     write(cunit) (ncvarindex(i), i=1,maxcvars)
387     write(cunit) (ncvarrecs(i), i=1,maxcvars)
388     write(cunit) (nx, i=1,maxcvars)
389     write(cunit) (ny, i=1,maxcvars)
390     write(cunit) (ncvarnrmax(i), i=1,maxcvars)
391     write(cunit) (ncvargrd(i), i=1,maxcvars)
392     write(cunit)
393    
394     #ifdef ALLOW_THETA0_CONTROL
395 heimbach 1.4.6.1 ivartype = 1
396     call ctrl_set_pack_xyz(
397     & cunit, ivartype, adfname_theta, "hFacC",
398     & wtheta, lxxadxx, mythid)
399 heimbach 1.1 #endif
400    
401     #ifdef ALLOW_SALT0_CONTROL
402 heimbach 1.4.6.1 ivartype = 2
403     call ctrl_set_pack_xyz(
404     & cunit, ivartype, adfname_salt, "hFacC",
405     & wsalt, lxxadxx, mythid)
406     #endif
407    
408     #ifdef ALLOW_HFLUX_CONTROL
409     ivartype = 3
410     write(weighttype(1:80),'(80a)') ' '
411     write(weighttype(1:80),'(a)') "whflux"
412     call ctrl_set_pack_xy(
413     & cunit, ivartype, adfname_hflux, "hFacC", weighttype,
414     & lxxadxx, mythid)
415     #endif
416    
417     #ifdef ALLOW_SFLUX_CONTROL
418     ivartype = 4
419     write(weighttype(1:80),'(80a)') ' '
420     write(weighttype(1:80),'(a)') "wsflux"
421     call ctrl_set_pack_xy(
422     & cunit, ivartype, adfname_sflux, "hFacC", weighttype,
423     & lxxadxx, mythid)
424     #endif
425    
426     #ifdef ALLOW_USTRESS_CONTROL
427     ivartype = 5
428     write(weighttype(1:80),'(80a)') ' '
429     write(weighttype(1:80),'(a)') "wtauu"
430     call ctrl_set_pack_xy(
431     & cunit, ivartype, adfname_tauu, "maskW", weighttype,
432     & lxxadxx, mythid)
433     #endif
434    
435     #ifdef ALLOW_VSTRESS_CONTROL
436     ivartype = 6
437     write(weighttype(1:80),'(80a)') ' '
438     write(weighttype(1:80),'(a)') "wtauv"
439     call ctrl_set_pack_xy(
440     & cunit, ivartype, adfname_tauv, "maskS", weighttype,
441     & lxxadxx, mythid)
442     #endif
443    
444     #ifdef ALLOW_ATEMP_CONTROL
445     ivartype = 7
446     write(weighttype(1:80),'(80a)') ' '
447     write(weighttype(1:80),'(a)') "watemp"
448     call ctrl_set_pack_xy(
449     & cunit, ivartype, adfname_atemp, "hFacC", weighttype,
450     & lxxadxx, mythid)
451     #endif
452    
453     #ifdef ALLOW_AQH_CONTROL
454     ivartype = 8
455     write(weighttype(1:80),'(80a)') ' '
456     write(weighttype(1:80),'(a)') "waqh"
457     call ctrl_set_pack_xy(
458     & cunit, ivartype, adfname_aqh, "hFacC", weighttype,
459     & lxxadxx, mythid)
460     #endif
461    
462     #ifdef ALLOW_UWIND_CONTROL
463     ivartype = 9
464     write(weighttype(1:80),'(80a)') ' '
465     write(weighttype(1:80),'(a)') "wuwind"
466     call ctrl_set_pack_xy(
467     & cunit, ivartype, adfname_uwind, "maskW", weighttype,
468     & lxxadxx, mythid)
469     #endif
470    
471     #ifdef ALLOW_VWIND_CONTROL
472     ivartype = 10
473     write(weighttype(1:80),'(80a)') ' '
474     write(weighttype(1:80),'(a)') "wvwind"
475     call ctrl_set_pack_xy(
476     & cunit, ivartype, adfname_vwind, "maskS", weighttype,
477     & lxxadxx, mythid)
478     #endif
479    
480     #ifdef ALLOW_OBCSN_CONTROL
481     ivartype = 11
482     call ctrl_set_pack_xz(
483     & cunit, ivartype, adfname_obcsn, "maskobcsn",
484     & wobcsn, lxxadxx, mythid)
485     #endif
486    
487     #ifdef ALLOW_OBCSS_CONTROL
488     ivartype = 12
489     call ctrl_set_pack_xz(
490     & cunit, ivartype, adfname_obcss, "maskobcss",
491     & wobcss, lxxadxx, mythid)
492     #endif
493    
494     #ifdef ALLOW_OBCSW_CONTROL
495     ivartype = 13
496     call ctrl_set_pack_yz(
497     & cunit, ivartype, adfname_obcsw, "maskobcsw",
498     & wobcsw, lxxadxx, mythid)
499     #endif
500    
501     #ifdef ALLOW_OBCSE_CONTROL
502     ivartype = 14
503     call ctrl_set_pack_yz(
504     & cunit, ivartype, adfname_obcse, "maskobcse",
505     & wobcse, lxxadxx, mythid)
506 heimbach 1.1 #endif
507    
508     close ( cunit )
509 heimbach 1.4.6.1
510 heimbach 1.1
511     return
512     end
513    

  ViewVC Help
Powered by ViewVC 1.1.22