/[MITgcm]/MITgcm/pkg/admtlm/admtlm_dsvd2model.F
ViewVC logotype

Annotation of /MITgcm/pkg/admtlm/admtlm_dsvd2model.F

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


Revision 1.4 - (hide annotations) (download)
Thu Feb 1 02:01:25 2007 UTC (17 years, 4 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint58w_post, checkpoint58x_post, checkpoint59, checkpoint58y_post, checkpoint58v_post
Changes since 1.3: +5 -11 lines
Updating ctrl variable names for depth control.

1 heimbach 1.2 C
2 heimbach 1.4 C $Header: /u/gcmpack/MITgcm/pkg/admtlm/admtlm_dsvd2model.F,v 1.3 2006/04/27 12:49:02 heimbach Exp $
3 heimbach 1.2 C $Name: $
4 heimbach 1.1
5 heimbach 1.2 #include "PACKAGES_CONFIG.h"
6     #include "CTRL_CPPOPTIONS.h"
7 heimbach 1.1
8 heimbach 1.3 subroutine admtlm_dsvd2model(
9     & first, postprocev, mythid )
10 heimbach 1.1
11 heimbach 1.2 c ==================================================================
12     c SUBROUTINE ctrl_unpack
13     c ==================================================================
14     c
15     c o Unpack the control vector such that the land points are filled
16     c in.
17     c
18     c started: Christian Eckert eckert@mit.edu 10-Mar-2000
19     c
20     c changed: Patrick Heimbach heimbach@mit.edu 06-Jun-2000
21     c - Transferred some filename declarations
22     c from here to namelist in ctrl_init
23     c
24     c Patrick Heimbach heimbach@mit.edu 16-Jun-2000
25     c - single file name convention with or without
26     c ALLOW_ECCO_OPTIMIZATION
27     C
28     c Armin Koehl akoehl@ucsd.edu 05-Dec-2000
29     c - single processor reads global parameter file
30     c and writes multiple xx* and adxx* files
31     c
32     c G Gebbie gebbie@mit.edu 18-Mar-2003
33     c - open boundary packing
34     c
35     c heimbach@mit.edu totally restructured 28-Oct-2003
36     c
37     c ==================================================================
38     c SUBROUTINE ctrl_unpack
39     c ==================================================================
40    
41     implicit none
42    
43     c == global variables ==
44    
45     #include "EEPARAMS.h"
46 heimbach 1.1 #include "SIZE.h"
47     #include "PARAMS.h"
48 heimbach 1.2 #include "GRID.h"
49    
50     #include "ctrl.h"
51     #include "optim.h"
52    
53     #ifdef ALLOW_COST
54     # include "cost.h"
55     #endif
56     #ifdef ALLOW_ECCO
57     # include "ecco_cost.h"
58     #else
59     # include "ctrl_weights.h"
60     #endif
61    
62     c == routine arguments ==
63    
64     logical first
65 heimbach 1.3 logical postprocev
66 heimbach 1.2 integer mythid
67    
68     #ifndef EXCLUDE_CTRL_PACK
69     c == local variables ==
70    
71     integer i, j, k
72     integer ii
73     integer il
74     integer irec
75     integer ivartype
76     integer ictrlgrad
77    
78     integer cbuffindex
79     integer cunit
80    
81     character*(128) cfile
82     character*( 80) weighttype
83    
84     logical lxxadxx
85    
86     cgg( Add OBCS mask names.
87     #ifdef ALLOW_OBCSN_CONTROL
88     integer filenWetobcsnGlo(nr,nobcs)
89     #endif
90     #ifdef ALLOW_OBCSS_CONTROL
91     integer filenWetobcssGlo(nr,nobcs)
92     #endif
93     #ifdef ALLOW_OBCSW_CONTROL
94     integer filenWetobcswGlo(nr,nobcs)
95     #endif
96     #ifdef ALLOW_OBCSE_CONTROL
97     integer filenWetobcseGlo(nr,nobcs)
98     #endif
99     integer iobcs
100     cgg)
101    
102     c == external ==
103    
104     integer ilnblnk
105     external ilnblnk
106    
107     c == end of interface ==
108    
109     #ifndef ALLOW_ECCO_OPTIMIZATION
110     fmin = 0. _d 0
111     #endif
112    
113     c-- Initialise
114     nbuffGlobal = 0
115    
116     cph-new(
117 heimbach 1.3 if ( postprocev ) then
118     yadprefix = 'ev'
119     else
120     yadprefix = 'g_'
121     endif
122 heimbach 1.2 nveccount = 0
123     cph-new)
124    
125     c-- Assign file names.
126    
127     call ctrl_set_fname(xx_theta_file, fname_theta, mythid)
128     call ctrl_set_fname(xx_salt_file, fname_salt, mythid)
129     call ctrl_set_fname(xx_hflux_file, fname_hflux, mythid)
130     call ctrl_set_fname(xx_sflux_file, fname_sflux, mythid)
131     call ctrl_set_fname(xx_tauu_file, fname_tauu, mythid)
132     call ctrl_set_fname(xx_tauv_file, fname_tauv, mythid)
133     call ctrl_set_fname(xx_atemp_file, fname_atemp, mythid)
134     call ctrl_set_fname(xx_aqh_file, fname_aqh, mythid)
135     call ctrl_set_fname(xx_precip_file, fname_precip, mythid)
136     call ctrl_set_fname(xx_swflux_file, fname_swflux, mythid)
137     call ctrl_set_fname(xx_swdown_file, fname_swdown, mythid)
138     call ctrl_set_fname(xx_uwind_file, fname_uwind, mythid)
139     call ctrl_set_fname(xx_vwind_file, fname_vwind, mythid)
140     call ctrl_set_fname(xx_obcsn_file, fname_obcsn, mythid)
141     call ctrl_set_fname(xx_obcss_file, fname_obcss, mythid)
142     call ctrl_set_fname(xx_obcsw_file, fname_obcsw, mythid)
143     call ctrl_set_fname(xx_obcse_file, fname_obcse, mythid)
144     call ctrl_set_fname(xx_diffkr_file, fname_diffkr, mythid)
145     call ctrl_set_fname(xx_kapgm_file, fname_kapgm, mythid)
146     call ctrl_set_fname(xx_tr1_file, fname_tr1, mythid)
147     call ctrl_set_fname(xx_sst_file, fname_sst, mythid)
148     call ctrl_set_fname(xx_sss_file, fname_sss, mythid)
149 heimbach 1.4 call ctrl_set_fname(xx_depth_file, fname_depth, mythid)
150 heimbach 1.2 call ctrl_set_fname(xx_efluxy_file, fname_efluxy, mythid)
151     call ctrl_set_fname(xx_efluxp_file, fname_efluxp, mythid)
152     call ctrl_set_fname(xx_bottomdrag_file, fname_bottomdrag, mythid)
153     call ctrl_set_fname(xx_edtaux_file, fname_edtaux, mythid)
154     call ctrl_set_fname(xx_edtauy_file, fname_edtauy, mythid)
155     call ctrl_set_fname(xx_uvel_file, fname_uvel, mythid)
156     call ctrl_set_fname(xx_vvel_file, fname_vvel, mythid)
157     call ctrl_set_fname(xx_etan_file, fname_etan, mythid)
158     call ctrl_set_fname(xx_relaxsst_file, fname_relaxsst, mythid)
159     call ctrl_set_fname(xx_relaxsss_file, fname_relaxsss, mythid)
160    
161     c-- Only the master thread will do I/O.
162     _BEGIN_MASTER( mythid )
163    
164     c *********************************************************************
165    
166     if ( first ) then
167     c >>> Initialise control vector for optimcycle=0 <<<
168     lxxadxx = .TRUE.
169     ictrlgrad = 1
170     write(cfile(1:128),'(4a,i4.4)')
171     & ctrlname(1:9),'_',yctrlid(1:10),
172     & yctrlposunpack(1:4), optimcycle
173     print *, 'ph-pack: unpacking ', ctrlname(1:9)
174     else
175     c >>> Write gradient vector <<<
176     lxxadxx = .FALSE.
177     ictrlgrad = 2
178     write(cfile(1:128),'(4a,i4.4)')
179     & costname(1:9),'_',yctrlid(1:10),
180     & yctrlposunpack(1:4), optimcycle
181     print *, 'ph-pack: unpacking ', costname(1:9)
182     endif
183    
184     call mdsfindunit( cunit, mythid )
185    
186 heimbach 1.1 #ifdef ALLOW_ADMTLM
187 heimbach 1.2
188 heimbach 1.3 if (postprocev) then
189     cph do a dummy read of initialized EV fields
190     cph they will be overwritten by array phtmpadmtlm
191     write(cfile(1:128),'(a)') ' '
192     write(cfile,'(a,i4.4)')
193     & 'admtlm_eigen', optimcycle
194     else
195     write(cfile(1:128),'(a)') ' '
196     write(cfile,'(a,i4.4)')
197     & 'admtlm_vector.it', optimcycle
198     endif
199 heimbach 1.2 print *, 'ph-pack: unpacking ', cfile
200 heimbach 1.3 cph open( cunit, file = cfile,
201     cph & status = 'old',
202     cph & form = 'unformatted',
203     cph & access = 'sequential' )
204 heimbach 1.2
205     #else /* ndef ALLOW_ADMTLM */
206    
207     open( cunit, file = cfile,
208     & status = 'old',
209     & form = 'unformatted',
210     & access = 'sequential' )
211    
212     c-- Header information.
213     read(cunit) filenvartype
214     read(cunit) filenvarlength
215     read(cunit) fileYctrlid
216     read(cunit) fileOptimCycle
217     read(cunit) filefc
218     read(cunit) fileIg
219     read(cunit) fileJg
220     read(cunit) filensx
221     read(cunit) filensy
222     read(cunit) (filenWetcGlobal(k), k=1,nr)
223     read(cunit) (filenWetsGlobal(k), k=1,nr)
224     read(cunit) (filenWetwGlobal(k), k=1,nr)
225     #ifdef ALLOW_CTRL_WETV
226     read(cunit) (filenWetvGlobal(k), k=1,nr)
227     #endif
228    
229     cgg( Add OBCS mask information to the header.
230     #ifdef ALLOW_OBCSN_CONTROL
231     read(cunit) ((filenWetobcsnGlo(k,iobcs),
232     & k=1,nr), iobcs= 1,nobcs)
233     #endif
234     #ifdef ALLOW_OBCSS_CONTROL
235     read(cunit) ((filenWetobcssGlo(k,iobcs),
236     & k=1,nr), iobcs= 1,nobcs)
237     #endif
238     #ifdef ALLOW_OBCSW_CONTROL
239     read(cunit) ((filenWetobcswGlo(k,iobcs),
240     & k=1,nr), iobcs= 1,nobcs)
241     #endif
242     #ifdef ALLOW_OBCSE_CONTROL
243     read(cunit) ((filenWetobcseGlo(k,iobcs),
244     & k=1,nr), iobcs= 1,nobcs)
245     #endif
246     cgg)
247     read(cunit) (filencvarindex(i), i=1,maxcvars)
248     read(cunit) (filencvarrecs(i), i=1,maxcvars)
249     read(cunit) (filencvarxmax(i), i=1,maxcvars)
250     read(cunit) (filencvarymax(i), i=1,maxcvars)
251     read(cunit) (filencvarnrmax(i), i=1,maxcvars)
252     read(cunit) (filencvargrd(i), i=1,maxcvars)
253     read(cunit)
254    
255     c Check file header info.
256     c
257     if ( filenvarlength .NE. nvarlength ) then
258     print *, 'WARNING: wrong nvarlength ',
259     & filenvarlength, nvarlength
260     STOP 'in S/R ctrl_unpack'
261     else if ( filensx .NE. nsx .OR. filensy .NE. nsy ) then
262     print *, 'WARNING: wrong nsx or nsy ',
263     & filensx, nsx, filensy, nsy
264     STOP 'in S/R ctrl_unpack'
265     endif
266     do k = 1, nr
267     if ( filenWetcGlobal(k) .NE. nWetcGlobal(k) .OR.
268     & filenWetsGlobal(k) .NE. nWetsGlobal(k) .OR.
269     & filenWetwGlobal(k) .NE. nWetwGlobal(k) .OR.
270     & filenWetvGlobal(k) .NE. nWetvGlobal(k) ) then
271     print *, 'WARNING: wrong nWet?Global for k = ', k
272     STOP
273     endif
274     end do
275    
276     cgg( Lets also check the OBCS mask info in the header.
277    
278     #ifdef ALLOW_OBCSN_CONTROL
279     do iobcs = 1, nobcs
280     do k = 1, nr
281     if (filenWetobcsnGlo(k,iobcs) .NE.
282     & nWetobcsnGlo(k,iobcs)) then
283     print *, 'WARNING: OBCSN wrong nWet?Global for k = ', k
284     STOP
285     endif
286     end do
287     end do
288     #endif
289    
290     #ifdef ALLOW_OBCSS_CONTROL
291     do iobcs = 1, nobcs
292     do k = 1, nr
293     if (filenWetobcssGlo(k,iobcs) .NE.
294     & nWetobcssGlo(k,iobcs)) then
295     print *, 'WARNING: OBCSS wrong nWet?Global for k = ', k
296     STOP
297     endif
298     end do
299     end do
300     #endif
301    
302     #ifdef ALLOW_OBCSW_CONTROL
303     do iobcs = 1, nobcs
304     do k = 1, nr
305     if (filenWetobcswGlo(k,iobcs) .NE.
306     & nWetobcswGlo(k,iobcs)) then
307     print *, 'WARNING: OBCSW wrong nWet?Global for k = ', k
308     STOP
309     endif
310     end do
311     end do
312     #endif
313    
314     #ifdef ALLOW_OBCSE_CONTROL
315     do iobcs = 1, nobcs
316     do k = 1, nr
317     if (filenWetobcseGlo(k,iobcs) .NE.
318     & nWetobcseGlo(k,iobcs)) then
319     print *, 'WARNING: OBCSE wrong nWet?Global for k = ', k
320     STOP
321     endif
322     end do
323     end do
324     #endif
325     cgg) End OBCS mask check.
326    
327     #endif /* ndef ALLOW_ADMTLM */
328    
329     c----------------------------------------------------------------------
330    
331     #ifdef ALLOW_THETA0_CONTROL
332     ivartype = 1
333     write(weighttype(1:80),'(80a)') ' '
334     write(weighttype(1:80),'(a)') "wtheta"
335     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
336     & fname_theta(ictrlgrad), "maskCtrlC",
337     & weighttype, wtheta, nwetcglobal, mythid)
338     #endif
339    
340     #ifdef ALLOW_SALT0_CONTROL
341     ivartype = 2
342     write(weighttype(1:80),'(80a)') ' '
343     write(weighttype(1:80),'(a)') "wsalt"
344     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
345     & fname_salt(ictrlgrad), "maskCtrlC",
346     & weighttype, wsalt, nwetcglobal, mythid)
347     #endif
348    
349     #if (defined (ALLOW_HFLUX_CONTROL) || defined (ALLOW_HFLUX0_CONTROL))
350     ivartype = 3
351     write(weighttype(1:80),'(80a)') ' '
352     write(weighttype(1:80),'(a)') "whflux"
353     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
354     & fname_hflux(ictrlgrad), "maskCtrlC",
355     & weighttype, nwetcglobal, mythid)
356 heimbach 1.1 #endif
357    
358 heimbach 1.2 #if (defined (ALLOW_SFLUX_CONTROL) || defined (ALLOW_SFLUX0_CONTROL))
359     ivartype = 4
360     write(weighttype(1:80),'(80a)') ' '
361     write(weighttype(1:80),'(a)') "wsflux"
362     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
363     & fname_sflux(ictrlgrad), "maskCtrlC",
364     & weighttype, nwetcglobal, mythid)
365     #endif
366    
367     #if (defined (ALLOW_USTRESS_CONTROL) || defined (ALLOW_TAUU0_CONTROL))
368     ivartype = 5
369     write(weighttype(1:80),'(80a)') ' '
370     write(weighttype(1:80),'(a)') "wtauu"
371     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
372     & fname_tauu(ictrlgrad), "maskCtrlW",
373     & weighttype, nwetwglobal, mythid)
374     #endif
375    
376     #if (defined (ALLOW_VSTRESS_CONTROL) || defined (ALLOW_TAUV0_CONTROL))
377     ivartype = 6
378     write(weighttype(1:80),'(80a)') ' '
379     write(weighttype(1:80),'(a)') "wtauv"
380     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
381     & fname_tauv(ictrlgrad), "maskCtrlS",
382     & weighttype, nwetsglobal, mythid)
383     #endif
384    
385     #ifdef ALLOW_ATEMP_CONTROL
386     ivartype = 7
387     write(weighttype(1:80),'(80a)') ' '
388     write(weighttype(1:80),'(a)') "watemp"
389     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
390     & fname_atemp(ictrlgrad), "maskCtrlC",
391     & weighttype, nwetcglobal, mythid)
392     #endif
393    
394     #ifdef ALLOW_AQH_CONTROL
395     ivartype = 8
396     write(weighttype(1:80),'(80a)') ' '
397     write(weighttype(1:80),'(a)') "waqh"
398     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
399     & fname_aqh(ictrlgrad), "maskCtrlC",
400     & weighttype, nwetcglobal, mythid)
401     #endif
402    
403     #ifdef ALLOW_UWIND_CONTROL
404     ivartype = 9
405     write(weighttype(1:80),'(80a)') ' '
406     write(weighttype(1:80),'(a)') "wuwind"
407     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
408     & fname_uwind(ictrlgrad), "maskCtrlC",
409     & weighttype, nwetcglobal, mythid)
410     #endif
411    
412     #ifdef ALLOW_VWIND_CONTROL
413     ivartype = 10
414     write(weighttype(1:80),'(80a)') ' '
415     write(weighttype(1:80),'(a)') "wvwind"
416     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
417     & fname_vwind(ictrlgrad), "maskCtrlC",
418     & weighttype, nwetcglobal, mythid)
419     #endif
420    
421     #ifdef ALLOW_OBCSN_CONTROL
422     ivartype = 11
423     write(weighttype(1:80),'(80a)') ' '
424     write(weighttype(1:80),'(a)') "wobcsn"
425     call ctrl_set_unpack_xz(
426     & cunit, ivartype, fname_obcsn(ictrlgrad), "maskobcsn",
427     & weighttype, wobcsn, nWetobcsnGlo, mythid)
428     #endif
429    
430     #ifdef ALLOW_OBCSS_CONTROL
431     ivartype = 12
432     write(weighttype(1:80),'(80a)') ' '
433     write(weighttype(1:80),'(a)') "wobcss"
434     call ctrl_set_unpack_xz(
435     & cunit, ivartype, fname_obcss(ictrlgrad), "maskobcss",
436     & weighttype, wobcss, nWetobcssGlo, mythid)
437     #endif
438    
439     #ifdef ALLOW_OBCSW_CONTROL
440     ivartype = 13
441     write(weighttype(1:80),'(80a)') ' '
442     write(weighttype(1:80),'(a)') "wobcsw"
443     call ctrl_set_unpack_yz(
444     & cunit, ivartype, fname_obcsw(ictrlgrad), "maskobcsw",
445     & weighttype, wobcsw, nWetobcswGlo, mythid)
446     #endif
447    
448     #ifdef ALLOW_OBCSE_CONTROL
449     ivartype = 14
450     write(weighttype(1:80),'(80a)') ' '
451     write(weighttype(1:80),'(a)') "wobcse"
452     call ctrl_set_unpack_yz(
453     & cunit, ivartype, fname_obcse(ictrlgrad), "maskobcse",
454     & weighttype, wobcse, nWetobcseGlo, mythid)
455     #endif
456    
457     #ifdef ALLOW_DIFFKR_CONTROL
458     ivartype = 15
459     write(weighttype(1:80),'(80a)') ' '
460     write(weighttype(1:80),'(a)') "wdiffkr"
461     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
462     & fname_diffkr(ictrlgrad), "maskCtrlC",
463     & weighttype, wunit, nwetcglobal, mythid)
464     #endif
465    
466     #ifdef ALLOW_KAPGM_CONTROL
467     ivartype = 16
468     write(weighttype(1:80),'(80a)') ' '
469     write(weighttype(1:80),'(a)') "wkapgm"
470     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
471     & fname_kapgm(ictrlgrad), "maskCtrlC",
472     & weighttype, wunit, nwetcglobal, mythid)
473     #endif
474    
475     #ifdef ALLOW_TR10_CONTROL
476     ivartype = 17
477     write(weighttype(1:80),'(80a)') ' '
478     write(weighttype(1:80),'(a)') "wtr1"
479     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
480     & fname_tr1(ictrlgrad), "maskCtrlC",
481     & weighttype, wunit, nwetcglobal, mythid)
482     #endif
483    
484     #if (defined (ALLOW_SST_CONTROL) || defined (ALLOW_SST0_CONTROL))
485     ivartype = 18
486     write(weighttype(1:80),'(80a)') ' '
487     write(weighttype(1:80),'(a)') "wsst"
488     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
489     & fname_sst(ictrlgrad), "maskCtrlC",
490     & weighttype, nwetcglobal, mythid)
491     #endif
492    
493     #if (defined (ALLOW_SSS_CONTROL) || defined (ALLOW_SSS0_CONTROL))
494     ivartype = 19
495     write(weighttype(1:80),'(80a)') ' '
496     write(weighttype(1:80),'(a)') "wsss"
497     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
498     & fname_sss(ictrlgrad), "maskCtrlC",
499     & weighttype, nwetcglobal, mythid)
500     #endif
501 heimbach 1.1
502 heimbach 1.4 #ifdef ALLOW_DEPTH_CONTROL
503 heimbach 1.2 ivartype = 20
504     write(weighttype(1:80),'(80a)') ' '
505 heimbach 1.4 write(weighttype(1:80),'(a)') "wdepth"
506 heimbach 1.2 call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
507 heimbach 1.4 & fname_depth(ictrlgrad), "maskCtrlC",
508 heimbach 1.2 & weighttype, weighttype, nwetcglobal, mythid)
509     #endif
510    
511     #ifdef ALLOW_EFLUXY0_CONTROL
512     ivartype = 21
513     write(weighttype(1:80),'(80a)') ' '
514     write(weighttype(1:80),'(a)') "wefluxy0"
515     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
516     & fname_efluxy(ictrlgrad), "maskCtrlS",
517     & weighttype, wefluxy, nwetsglobal, mythid)
518     #endif
519    
520     #ifdef ALLOW_EFLUXP0_CONTROL
521     ivartype = 22
522     write(weighttype(1:80),'(80a)') ' '
523     write(weighttype(1:80),'(a)') "wefluxp0"
524     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
525     & fname_efluxp(ictrlgrad), "maskhFacV",
526     & weighttype, wefluxp, nwetvglobal, mythid)
527     #endif
528    
529     #ifdef ALLOW_BOTTOMDRAG_CONTROL
530     ivartype = 23
531     write(weighttype(1:80),'(80a)') ' '
532     write(weighttype(1:80),'(a)') "wbottomdrag"
533     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
534     & fname_bottomdrag(ictrlgrad), "maskCtrlC",
535     & weighttype, nwetcglobal, mythid)
536     #endif
537    
538     #ifdef ALLOW_EDTAUX_CONTROL
539     ivartype = 25
540     write(weighttype(1:80),'(80a)') ' '
541     write(weighttype(1:80),'(a)') "wedtaux"
542     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
543     & fname_edtaux(ictrlgrad), "maskCtrlW",
544     & weighttype, wunit, nwetwglobal, mythid)
545     #endif
546    
547     #ifdef ALLOW_EDTAUY_CONTROL
548     ivartype = 26
549     write(weighttype(1:80),'(80a)') ' '
550     write(weighttype(1:80),'(a)') "wedtauy"
551     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
552     & fname_edtauy(ictrlgrad), "maskCtrlS",
553     & weighttype, wunit, nwetsglobal, mythid)
554     #endif
555    
556     #ifdef ALLOW_UVEL0_CONTROL
557     ivartype = 27
558     write(weighttype(1:80),'(80a)') ' '
559     write(weighttype(1:80),'(a)') "wuvel"
560     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
561     & fname_uvel(ictrlgrad), "maskCtrlW",
562     & weighttype, wunit, nwetwglobal, mythid)
563     #endif
564    
565     #ifdef ALLOW_VVEL0_CONTROL
566     ivartype = 28
567     write(weighttype(1:80),'(80a)') ' '
568     write(weighttype(1:80),'(a)') "wvvel"
569     call ctrl_set_unpack_xyz( lxxadxx, cunit, ivartype,
570     & fname_vvel(ictrlgrad), "maskCtrlS",
571     & weighttype, wunit, nwetsglobal, mythid)
572     #endif
573    
574     #ifdef ALLOW_ETAN0_CONTROL
575     ivartype = 29
576     write(weighttype(1:80),'(80a)') ' '
577     write(weighttype(1:80),'(a)') "wetan"
578     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
579     & fname_etan(ictrlgrad), "maskCtrlC",
580     & weighttype, nwetcglobal, mythid)
581     #endif
582    
583     #ifdef ALLOW_RELAXSST_CONTROL
584     ivartype = 30
585     write(weighttype(1:80),'(80a)') ' '
586     write(weighttype(1:80),'(a)') "wrelaxsst"
587     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
588     & fname_relaxsst(ictrlgrad), "maskCtrlC",
589     & weighttype, nwetcglobal, mythid)
590     #endif
591    
592     #ifdef ALLOW_RELAXSSS_CONTROL
593     ivartype = 31
594     write(weighttype(1:80),'(80a)') ' '
595     write(weighttype(1:80),'(a)') "wrelaxsss"
596     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
597     & fname_relaxsss(ictrlgrad), "maskCtrlC",
598     & weighttype, nwetcglobal, mythid)
599     #endif
600    
601     #ifdef ALLOW_PRECIP_CONTROL
602     ivartype = 32
603     write(weighttype(1:80),'(80a)') ' '
604     write(weighttype(1:80),'(a)') "wprecip"
605     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
606     & fname_precip(ictrlgrad), "maskCtrlC",
607     & weighttype, nwetcglobal, mythid)
608     #endif
609    
610     #ifdef ALLOW_SWFLUX_CONTROL
611     ivartype = 33
612     write(weighttype(1:80),'(80a)') ' '
613     write(weighttype(1:80),'(a)') "wswflux"
614     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
615     & fname_swflux(ictrlgrad), "maskCtrlC",
616     & weighttype, nwetcglobal, mythid)
617     #endif
618 heimbach 1.1
619 heimbach 1.2 #ifdef ALLOW_SWDOWN_CONTROL
620     ivartype = 34
621     write(weighttype(1:80),'(80a)') ' '
622     write(weighttype(1:80),'(a)') "wswdown"
623     call ctrl_set_unpack_xy( lxxadxx, cunit, ivartype,
624     & fname_swdown(ictrlgrad), "maskCtrlC",
625     & weighttype, nwetcglobal, mythid)
626 heimbach 1.1 #endif
627 heimbach 1.2
628     close ( cunit )
629    
630     _END_MASTER( mythid )
631    
632     #endif /* EXCLUDE_CTRL_PACK */
633    
634     return
635 heimbach 1.1 end
636 heimbach 1.2

  ViewVC Help
Powered by ViewVC 1.1.22