/[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 - (hide annotations) (download)
Fri Sep 28 15:15:55 2001 UTC (22 years, 8 months ago) by heimbach
Branch: MAIN
CVS Tags: checkpoint44e_post, checkpoint44f_post, checkpoint43a-release1mods, chkpt44d_post, release1_p1, release1_p2, release1_p3, release1_p4, checkpoint44e_pre, release1_b1, checkpoint43, release1_chkpt44d_post, release1-branch_tutorials, checkpoint45d_post, chkpt44a_post, checkpoint44h_pre, chkpt44c_pre, checkpoint45a_post, checkpoint44g_post, checkpoint45b_post, release1-branch-end, release1_final_v1, checkpoint44b_post, checkpoint45c_post, checkpoint44h_post, chkpt44a_pre, release1_beta1, checkpoint44b_pre, checkpoint44, checkpoint45, chkpt44c_post, checkpoint44f_pre, release1-branch_branchpoint
Branch point for: release1_final, release1-branch, release1, ecco-branch, release1_coupled
Changes since 1.3: +25 -37 lines
Adding basic comments to ctrl package.

1 heimbach 1.4 C $Header: /u/gcmpack/models/MITgcmUV/pkg/ctrl/ctrl_pack.F,v 1.3 2001/08/13 18:10:26 heimbach Exp $
2 heimbach 1.1
3     #include "CTRL_CPPOPTIONS.h"
4    
5 heimbach 1.4 CBOP
6     C !ROUTINE: ctrl_pack
7     C !INTERFACE:
8     subroutine ctrl_pack( myiter, mytime, mythid )
9    
10     C !DESCRIPTION: \bv
11     c *=================================================================
12     c | SUBROUTINE ctrl_pack
13     c | Pack the control vector
14     c | * All control variable and adjoint variable fields are
15     c | read from disk.
16     c | * Wet points are extracted, and elements are
17     c | normalized (optional)
18     c | * A single control vector containing only (normalized
19     c | wet points is written to file.
20     c *=================================================================
21     C \ev
22 heimbach 1.1
23 heimbach 1.4 C !USES:
24 heimbach 1.1 implicit none
25    
26     c == global variables ==
27     #include "EEPARAMS.h"
28     #include "SIZE.h"
29     #include "PARAMS.h"
30     #include "GRID.h"
31     #include "ctrl.h"
32     #include "cost.h"
33 heimbach 1.2 #include "optim.h"
34 heimbach 1.1
35 heimbach 1.4 C !INPUT/OUTPUT PARAMETERS:
36 heimbach 1.1 c == routine arguments ==
37     integer myiter
38     _RL mytime
39     integer mythid
40    
41 heimbach 1.4 C !LOCAL VARIABLES:
42 heimbach 1.1 c == local variables ==
43    
44     integer bi,bj
45     integer ip,jp
46     integer i,j,k
47     integer ii
48     integer il
49     integer irec
50     integer itlo,ithi
51     integer jtlo,jthi
52     integer jmin,jmax
53     integer imin,imax
54 heimbach 1.4 integer cbuffindex
55     integer cunit
56     integer prec
57 heimbach 1.1
58     logical doglobalread
59     logical ladinit
60    
61     _RL cbuff( snx*nsx*npx*sny*nsy*npy )
62     _RL globfld3d( snx,nsx,npx,sny,nsy,npy,nr )
63     _RL globfld2d( snx,nsx,npx,sny,nsy,npy )
64     _RL globmsk( snx,nsx,npx,sny,nsy,npy,nr )
65     _RL tmpvar
66    
67     character*(128) cfile
68     character*( 80) fname
69    
70     c == external ==
71     integer ilnblnk
72     external ilnblnk
73    
74     c == end of interface ==
75 heimbach 1.4 CEOP
76 heimbach 1.1
77     prec = precFloat64
78     tmpvar = -9999. _d 0
79    
80     jtlo = 1
81     jthi = nsy
82     itlo = 1
83     ithi = nsx
84     jmin = 1
85     jmax = sny
86     imin = 1
87     imax = snx
88    
89     c-- Tiled files are used.
90     doglobalread = .false.
91    
92     c-- Initialise adjoint variables on active files.
93     ladinit = .false.
94    
95     c
96     c-- Only the master thread will do I/O.
97     _BEGIN_MASTER( mythid )
98    
99     c-- read global mask file
100     call MDSREADFIELD_3D_GL( "hFacC",
101     & prec, 'RL', Nr, globmsk,
102     & 1, mythid)
103    
104    
105     c >>> Write control vector <<<
106    
107     call mdsfindunit( cunit, mythid )
108     write(cfile(1:128),'(2a,i4.4)')
109     & ctrlname(1:9),'.opt',
110     & optimcycle
111    
112     open( cunit, file = cfile,
113     & status = 'unknown',
114     & form = 'unformatted',
115     & access = 'sequential' )
116    
117     c-- Header information.
118    
119     write(cunit) nvartype
120     write(cunit) nvarlength
121     write(cunit) expId
122     write(cunit) optimCycle
123     write(cunit) tmpvar
124     write(cunit) 1
125     write(cunit) 1
126     write(cunit) 1
127     write(cunit) 1
128     write(cunit) (nWetcTile(1,1,k), k=1,nr)
129     write(cunit) (nWetsTile(1,1,k), k=1,nr)
130     write(cunit) (nWetwTile(1,1,k), k=1,nr)
131     write(cunit) (ncvarindex(i), i=1,maxcvars)
132     write(cunit) (ncvarrecs(i), i=1,maxcvars)
133     write(cunit) (nx, i=1,maxcvars)
134     write(cunit) (ny, i=1,maxcvars)
135     write(cunit) (ncvarnrmax(i), i=1,maxcvars)
136     write(cunit) (ncvargrd(i), i=1,maxcvars)
137     write(cunit)
138    
139     #ifdef ALLOW_THETA0_CONTROL
140    
141     il=ilnblnk( xx_theta_file)
142     write(fname(1:80),'(80a)') ' '
143     write(fname(1:80),'(2a,i10.10)')
144     & xx_theta_file(1:il),'.',optimcycle
145     call MDSREADFIELD_3D_GL( fname,
146     & prec, 'RL', Nr, globfld3d,
147     & 1, mythid)
148    
149     write(cunit) ncvarindex(1)
150     write(cunit) 1
151     write(cunit) 1
152     do k = 1,nr
153     cbuffindex = 0
154     do jp = 1,nPy
155     do bj = jtlo,jthi
156     do j = jmin,jmax
157     do ip = 1,nPx
158     do bi = itlo,ithi
159     do i = imin,imax
160     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
161     cbuffindex = cbuffindex + 1
162     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
163     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
164     & * sqrt(wtheta(k,bi,bj))
165     #else
166     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
167     #endif
168     endif
169     enddo
170     enddo
171     enddo
172     enddo
173     enddo
174     enddo
175     c --> check cbuffindex.
176     if ( cbuffindex .gt. 0) then
177     write(cunit) cbuffindex
178     write(cunit) k
179     write(cunit) (cbuff(ii), ii=1,cbuffindex)
180     endif
181     enddo
182    
183     #endif
184    
185     #ifdef ALLOW_SALT0_CONTROL
186    
187     il=ilnblnk( xx_salt_file)
188     write(fname(1:80),'(80a)') ' '
189     write(fname(1:80),'(2a,i10.10)')
190     & xx_salt_file(1:il),'.',optimcycle
191     call MDSREADFIELD_3D_GL( fname,
192     & prec, 'RL', Nr, globfld3d,
193     & 1, mythid)
194    
195     write(cunit) ncvarindex(2)
196     write(cunit) 1
197     write(cunit) 1
198     do k = 1,nr
199     cbuffindex = 0
200     do jp = 1,nPy
201     do bj = jtlo,jthi
202     do j = jmin,jmax
203     do ip = 1,nPx
204     do bi = itlo,ithi
205     do i = imin,imax
206     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
207     cbuffindex = cbuffindex + 1
208     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
209     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
210     & * sqrt(wsalt(k,bi,bj))
211     #else
212     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
213     #endif
214     endif
215     enddo
216     enddo
217     enddo
218     enddo
219     enddo
220     enddo
221     c --> check cbuffindex.
222     if ( cbuffindex .gt. 0) then
223     write(cunit) cbuffindex
224     write(cunit) k
225     write(cunit) (cbuff(ii), ii=1,cbuffindex)
226     endif
227     enddo
228    
229     #endif
230    
231 heimbach 1.2 #ifdef ALLOW_TR10_CONTROL
232    
233     il=ilnblnk( xx_tr1_file)
234     write(fname(1:80),'(80a)') ' '
235     write(fname(1:80),'(2a,i10.10)')
236     & xx_tr1_file(1:il),'.',optimcycle
237     call MDSREADFIELD_3D_GL( fname,
238     & prec, 'RL', Nr, globfld3d,
239     & 1, mythid)
240    
241     write(cunit) ncvarindex(9)
242     write(cunit) 1
243     write(cunit) 1
244     do k = 1,nr
245     cbuffindex = 0
246     do jp = 1,nPy
247     do bj = jtlo,jthi
248     do j = jmin,jmax
249     do ip = 1,nPx
250     do bi = itlo,ithi
251     do i = imin,imax
252     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
253     cbuffindex = cbuffindex + 1
254     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
255     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
256     cph & * sqrt(wtr1(k,bi,bj))
257     #else
258     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
259     #endif
260     endif
261     enddo
262     enddo
263     enddo
264     enddo
265     enddo
266     enddo
267     c --> check cbuffindex.
268     if ( cbuffindex .gt. 0) then
269     write(cunit) cbuffindex
270     write(cunit) k
271     write(cunit) (cbuff(ii), ii=1,cbuffindex)
272     endif
273     enddo
274    
275     #endif
276    
277 heimbach 1.1 #ifdef ALLOW_HFLUX0_CONTROL
278    
279     il=ilnblnk( xx_hflux_file)
280     write(fname(1:80),'(80a)') ' '
281     write(fname(1:80),'(2a,i10.10)')
282     & xx_hflux_file(1:il),'.',optimcycle
283     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
284     call MDSREADFIELD_2D_GL( "whflux",
285     & prec, 'RL', 1,
286     & globfld2d,
287     & 1, mythid)
288     #endif
289     call MDSREADFIELD_2D_GL( fname,
290     & prec, 'RL', 1,
291     & globfld3d(1,1,1,1,1,1,1),
292     & 1, mythid)
293    
294     write(cunit) ncvarindex(3)
295     write(cunit) 1
296     write(cunit) 1
297     k = 1
298     cbuffindex = 0
299     do jp = 1,nPy
300     do bj = jtlo,jthi
301     do j = jmin,jmax
302     do ip = 1,nPx
303     do bi = itlo,ithi
304     do i = imin,imax
305     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
306     cbuffindex = cbuffindex + 1
307     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
308     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
309     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
310     #else
311     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
312     #endif
313     endif
314     enddo
315     enddo
316     enddo
317     enddo
318     enddo
319     enddo
320     c --> check cbuffindex.
321     if ( cbuffindex .gt. 0) then
322     write(cunit) cbuffindex
323     write(cunit) k
324     write(cunit) (cbuff(ii), ii=1,cbuffindex)
325     endif
326    
327     #endif
328    
329     #ifdef ALLOW_SFLUX0_CONTROL
330    
331     il=ilnblnk( xx_sflux_file)
332     write(fname(1:80),'(80a)') ' '
333     write(fname(1:80),'(2a,i10.10)')
334     & xx_sflux_file(1:il),'.',optimcycle
335     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
336     call MDSREADFIELD_2D_GL( "wsflux",
337     & prec, 'RL', 1,
338     & globfld2d,
339     & 1, mythid)
340     #endif
341     call MDSREADFIELD_2D_GL( fname,
342     & prec, 'RL', 1,
343     & globfld3d(1,1,1,1,1,1,1),
344     & 1, mythid)
345    
346     write(cunit) ncvarindex(4)
347     write(cunit) 1
348     write(cunit) 1
349     k = 1
350     cbuffindex = 0
351     do jp = 1,nPy
352     do bj = jtlo,jthi
353     do j = jmin,jmax
354     do ip = 1,nPx
355     do bi = itlo,ithi
356     do i = imin,imax
357     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
358     cbuffindex = cbuffindex + 1
359     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
360     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
361     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
362     #else
363     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
364     #endif
365     endif
366     enddo
367     enddo
368     enddo
369     enddo
370     enddo
371     enddo
372     c --> check cbuffindex.
373     if ( cbuffindex .gt. 0) then
374     write(cunit) cbuffindex
375     write(cunit) k
376     write(cunit) (cbuff(ii), ii=1,cbuffindex)
377     endif
378    
379     #endif
380    
381     #ifdef ALLOW_TAUU0_CONTROL
382    
383     il=ilnblnk( xx_tauu_file)
384     write(fname(1:80),'(80a)') ' '
385     write(fname(1:80),'(2a,i10.10)')
386     & xx_tauu_file(1:il),'.',optimcycle
387     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
388     call MDSREADFIELD_2D_GL( "wtauu",
389     & prec, 'RL', 1,
390     & globfld2d,
391     & 1, mythid)
392     #endif
393     call MDSREADFIELD_2D_GL( fname,
394     & prec, 'RL', 1,
395     & globfld3d(1,1,1,1,1,1,1),
396     & 1, mythid)
397    
398     write(cunit) ncvarindex(5)
399     write(cunit) 1
400     write(cunit) 1
401     k = 1
402     cbuffindex = 0
403     do jp = 1,nPy
404     do bj = jtlo,jthi
405     do j = jmin,jmax
406     do ip = 1,nPx
407     do bi = itlo,ithi
408     do i = imin,imax
409     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
410     cbuffindex = cbuffindex + 1
411     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
412     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
413     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
414     #else
415     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
416     #endif
417     endif
418     enddo
419     enddo
420     enddo
421     enddo
422     enddo
423     enddo
424     c --> check cbuffindex.
425     if ( cbuffindex .gt. 0) then
426     write(cunit) cbuffindex
427     write(cunit) k
428     write(cunit) (cbuff(ii), ii=1,cbuffindex)
429     endif
430    
431     #endif
432    
433     #ifdef ALLOW_TAUV0_CONTROL
434    
435     il=ilnblnk( xx_tauv_file)
436     write(fname(1:80),'(80a)') ' '
437     write(fname(1:80),'(2a,i10.10)')
438     & xx_tauv_file(1:il),'.',optimcycle
439     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
440     call MDSREADFIELD_2D_GL( "wtauv",
441     & prec, 'RL', 1,
442     & globfld2d,
443     & 1, mythid)
444     #endif
445     call MDSREADFIELD_2D_GL( fname,
446     & prec, 'RL', 1,
447     & globfld3d(1,1,1,1,1,1,1),
448     & 1, mythid)
449    
450     write(cunit) ncvarindex(6)
451     write(cunit) 1
452     write(cunit) 1
453     k = 1
454     cbuffindex = 0
455     do jp = 1,nPy
456     do bj = jtlo,jthi
457     do j = jmin,jmax
458     do ip = 1,nPx
459     do bi = itlo,ithi
460     do i = imin,imax
461     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
462     cbuffindex = cbuffindex + 1
463     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
464     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
465     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
466     #else
467     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
468     #endif
469     endif
470     enddo
471     enddo
472     enddo
473     enddo
474     enddo
475     enddo
476     c --> check cbuffindex.
477     if ( cbuffindex .gt. 0) then
478     write(cunit) cbuffindex
479     write(cunit) k
480     write(cunit) (cbuff(ii), ii=1,cbuffindex)
481     endif
482    
483     #endif
484    
485     #ifdef ALLOW_SST0_CONTROL
486    
487     il=ilnblnk( xx_sst_file)
488     write(fname(1:80),'(80a)') ' '
489     write(fname(1:80),'(2a,i10.10)')
490     & xx_sst_file(1:il),'.',optimcycle
491     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
492     call MDSREADFIELD_2D_GL( "wsst",
493     & prec, 'RL', 1,
494     & globfld2d,
495     & 1, mythid)
496     #endif
497     call MDSREADFIELD_2D_GL( fname,
498     & prec, 'RL', 1,
499     & globfld3d(1,1,1,1,1,1,1),
500     & 1, mythid)
501    
502     write(cunit) ncvarindex(7)
503     write(cunit) 1
504     write(cunit) 1
505     k = 1
506     cbuffindex = 0
507     do jp = 1,nPy
508     do bj = jtlo,jthi
509     do j = jmin,jmax
510     do ip = 1,nPx
511     do bi = itlo,ithi
512     do i = imin,imax
513     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
514     cbuffindex = cbuffindex + 1
515     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
516     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
517     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
518     #else
519     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
520     #endif
521     endif
522     enddo
523     enddo
524     enddo
525     enddo
526     enddo
527     enddo
528     c --> check cbuffindex.
529     if ( cbuffindex .gt. 0) then
530     write(cunit) cbuffindex
531     write(cunit) k
532     write(cunit) (cbuff(ii), ii=1,cbuffindex)
533     endif
534    
535     #endif
536    
537     #ifdef ALLOW_SSS0_CONTROL
538    
539     il=ilnblnk( xx_sss_file)
540     write(fname(1:80),'(80a)') ' '
541     write(fname(1:80),'(2a,i10.10)')
542     & xx_sss_file(1:il),'.',optimcycle
543     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
544     call MDSREADFIELD_2D_GL( "wsss",
545     & prec, 'RL', 1,
546     & globfld2d,
547     & 1, mythid)
548     #endif
549     call MDSREADFIELD_2D_GL( fname,
550     & prec, 'RL', 1,
551     & globfld3d(1,1,1,1,1,1,1),
552     & 1, mythid)
553    
554     write(cunit) ncvarindex(8)
555     write(cunit) 1
556     write(cunit) 1
557     k = 1
558     cbuffindex = 0
559     do jp = 1,nPy
560     do bj = jtlo,jthi
561     do j = jmin,jmax
562     do ip = 1,nPx
563     do bi = itlo,ithi
564     do i = imin,imax
565     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
566     cbuffindex = cbuffindex + 1
567     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
568     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
569     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
570     #else
571     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
572     #endif
573     endif
574     enddo
575     enddo
576     enddo
577     enddo
578     enddo
579     enddo
580     c --> check cbuffindex.
581     if ( cbuffindex .gt. 0) then
582     write(cunit) cbuffindex
583     write(cunit) k
584     write(cunit) (cbuff(ii), ii=1,cbuffindex)
585     endif
586    
587     #endif
588    
589 heimbach 1.3 #ifdef ALLOW_DIFFKR_CONTROL
590    
591     il=ilnblnk( xx_diffkr_file)
592     write(fname(1:80),'(80a)') ' '
593     write(fname(1:80),'(2a,i10.10)')
594     & xx_diffkr_file(1:il),'.',optimcycle
595     call MDSREADFIELD_3D_GL( fname,
596     & prec, 'RL', Nr, globfld3d,
597     & 1, mythid)
598    
599     write(cunit) ncvarindex(15)
600     write(cunit) 1
601     write(cunit) 1
602     do k = 1,nr
603     cbuffindex = 0
604     do jp = 1,nPy
605     do bj = jtlo,jthi
606     do j = jmin,jmax
607     do ip = 1,nPx
608     do bi = itlo,ithi
609     do i = imin,imax
610     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
611     cbuffindex = cbuffindex + 1
612     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
613     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
614     cph & * sqrt(wdiffkr(k,bi,bj))
615     #else
616     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
617     #endif
618     endif
619     enddo
620     enddo
621     enddo
622     enddo
623     enddo
624     enddo
625     c --> check cbuffindex.
626     if ( cbuffindex .gt. 0) then
627     write(cunit) cbuffindex
628     write(cunit) k
629     write(cunit) (cbuff(ii), ii=1,cbuffindex)
630     endif
631     enddo
632    
633     #endif
634    
635     #ifdef ALLOW_KAPGM_CONTROL
636    
637     il=ilnblnk( xx_kapgm_file)
638     write(fname(1:80),'(80a)') ' '
639     write(fname(1:80),'(2a,i10.10)')
640     & xx_kapgm_file(1:il),'.',optimcycle
641     call MDSREADFIELD_3D_GL( fname,
642     & prec, 'RL', Nr, globfld3d,
643     & 1, mythid)
644    
645     write(cunit) ncvarindex(16)
646     write(cunit) 1
647     write(cunit) 1
648     do k = 1,nr
649     cbuffindex = 0
650     do jp = 1,nPy
651     do bj = jtlo,jthi
652     do j = jmin,jmax
653     do ip = 1,nPx
654     do bi = itlo,ithi
655     do i = imin,imax
656     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
657     cbuffindex = cbuffindex + 1
658     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
659     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
660     cph & * sqrt(wkapgm(k,bi,bj))
661     #else
662     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
663     #endif
664     endif
665     enddo
666     enddo
667     enddo
668     enddo
669     enddo
670     enddo
671     c --> check cbuffindex.
672     if ( cbuffindex .gt. 0) then
673     write(cunit) cbuffindex
674     write(cunit) k
675     write(cunit) (cbuff(ii), ii=1,cbuffindex)
676     endif
677     enddo
678    
679     #endif
680 heimbach 1.1
681     close ( cunit )
682    
683     _END_MASTER( mythid )
684    
685     c======================================================================
686    
687     c-- read global mask file
688     call MDSREADFIELD_3D_GL( "hFacC",
689     & prec, 'RL', Nr, globmsk,
690     & 1, mythid)
691    
692     c >>> Write gradient vector <<<
693    
694     call mdsfindunit( cunit, mythid )
695     write(cfile(1:128),'(2a,i4.4)')
696     & costname(1:9),'.opt',
697     & optimcycle
698    
699     open( cunit, file = cfile,
700     & status = 'unknown',
701     & form = 'unformatted',
702     & access = 'sequential' )
703    
704     c-- Header information.
705     write(cunit) nvartype
706     write(cunit) nvarlength
707     write(cunit) expId
708     write(cunit) optimCycle
709     write(cunit) fc
710     write(cunit) 1
711     write(cunit) 1
712     write(cunit) 1
713     write(cunit) 1
714     write(cunit) (nWetcTile(1,1,k), k=1,nr)
715     write(cunit) (nWetsTile(1,1,k), k=1,nr)
716     write(cunit) (nWetwTile(1,1,k), k=1,nr)
717     write(cunit) (ncvarindex(i), i=1,maxcvars)
718     write(cunit) (ncvarrecs(i), i=1,maxcvars)
719     write(cunit) (nx, i=1,maxcvars)
720     write(cunit) (ny, i=1,maxcvars)
721     write(cunit) (ncvarnrmax(i), i=1,maxcvars)
722     write(cunit) (ncvargrd(i), i=1,maxcvars)
723     write(cunit)
724    
725     #ifdef ALLOW_THETA0_CONTROL
726    
727     il=ilnblnk( xx_theta_file)
728     write(fname(1:80),'(80a)') ' '
729     write(fname(1:80),'(3a,i10.10)')
730     & yadmark,xx_theta_file(1:il),'.',optimcycle
731    
732     call MDSREADFIELD_3D_GL( fname,
733     & prec, 'RL', Nr,
734     & globfld3d,
735     & 1, mythid)
736    
737     write(cunit) ncvarindex(1)
738     write(cunit) 1
739     write(cunit) 1
740     do k = 1,nr
741     cbuffindex = 0
742     do jp = 1,nPy
743     do bj = jtlo,jthi
744     do j = jmin,jmax
745     do ip = 1,nPx
746     do bi = itlo,ithi
747     do i = imin,imax
748     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
749     cbuffindex = cbuffindex + 1
750     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
751     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
752     & * sqrt(wtheta(k,bi,bj))
753     #else
754     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
755     #endif
756     endif
757     enddo
758     enddo
759     enddo
760     enddo
761     enddo
762     enddo
763     c --> check cbuffindex.
764     if ( cbuffindex .gt. 0) then
765     write(cunit) cbuffindex
766     write(cunit) k
767     write(cunit) (cbuff(ii), ii=1,cbuffindex)
768     endif
769     enddo
770    
771     #endif
772    
773     #ifdef ALLOW_SALT0_CONTROL
774    
775     il=ilnblnk( xx_salt_file)
776     write(fname(1:80),'(80a)') ' '
777     write(fname(1:80),'(3a,i10.10)')
778     & yadmark,xx_salt_file(1:il),'.',optimcycle
779    
780     call MDSREADFIELD_3D_GL( fname,
781     & prec, 'RL', Nr,
782     & globfld3d,
783     & 1, mythid)
784    
785     write(cunit) ncvarindex(2)
786     write(cunit) 1
787     write(cunit) 1
788     do k = 1,nr
789     cbuffindex = 0
790     do jp = 1,nPy
791     do bj = jtlo,jthi
792     do j = jmin,jmax
793     do ip = 1,nPx
794     do bi = itlo,ithi
795     do i = imin,imax
796     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
797     cbuffindex = cbuffindex + 1
798     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
799     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
800     & * sqrt(wsalt(k,bi,bj))
801     #else
802     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
803     #endif
804     endif
805     enddo
806     enddo
807     enddo
808     enddo
809     enddo
810     enddo
811     c --> check cbuffindex.
812     if ( cbuffindex .gt. 0) then
813     write(cunit) cbuffindex
814     write(cunit) k
815     write(cunit) (cbuff(ii), ii=1,cbuffindex)
816     endif
817     enddo
818    
819     #endif
820    
821 heimbach 1.2 #ifdef ALLOW_TR10_CONTROL
822    
823     il=ilnblnk( xx_tr1_file)
824     write(fname(1:80),'(80a)') ' '
825     write(fname(1:80),'(3a,i10.10)')
826     & yadmark,xx_tr1_file(1:il),'.',optimcycle
827    
828     call MDSREADFIELD_3D_GL( fname,
829     & prec, 'RL', Nr,
830     & globfld3d,
831     & 1, mythid)
832    
833     write(cunit) ncvarindex(9)
834     write(cunit) 1
835     write(cunit) 1
836     do k = 1,nr
837     cbuffindex = 0
838     do jp = 1,nPy
839     do bj = jtlo,jthi
840     do j = jmin,jmax
841     do ip = 1,nPx
842     do bi = itlo,ithi
843     do i = imin,imax
844     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
845     cbuffindex = cbuffindex + 1
846     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
847     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
848     cph & * sqrt(wtr1(k,bi,bj))
849     #else
850     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
851     #endif
852     endif
853     enddo
854     enddo
855     enddo
856     enddo
857     enddo
858     enddo
859     c --> check cbuffindex.
860     if ( cbuffindex .gt. 0) then
861     write(cunit) cbuffindex
862     write(cunit) k
863     write(cunit) (cbuff(ii), ii=1,cbuffindex)
864     endif
865     enddo
866    
867     #endif
868 heimbach 1.1
869     #ifdef ALLOW_HFLUX0_CONTROL
870    
871     il=ilnblnk( xx_hflux_file)
872     write(fname(1:80),'(80a)') ' '
873     write(fname(1:80),'(3a,i10.10)')
874     & yadmark,xx_hflux_file(1:il),'.',optimcycle
875     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
876     call MDSREADFIELD_2D_GL( "whflux",
877     & prec, 'RL', 1,
878     & globfld2d,
879     & 1, mythid)
880     #endif
881     call MDSREADFIELD_2D_GL( fname,
882     & prec, 'RL', 1,
883     & globfld3d(1,1,1,1,1,1,1),
884     & 1, mythid)
885    
886     write(cunit) ncvarindex(3)
887     write(cunit) 1
888     write(cunit) 1
889     k = 1
890     cbuffindex = 0
891     do jp = 1,nPy
892     do bj = jtlo,jthi
893     do j = jmin,jmax
894     do ip = 1,nPx
895     do bi = itlo,ithi
896     do i = imin,imax
897     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
898     cbuffindex = cbuffindex + 1
899     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
900     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
901     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
902     #else
903     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
904     #endif
905     endif
906     enddo
907     enddo
908     enddo
909     enddo
910     enddo
911     enddo
912     c --> check cbuffindex.
913     if ( cbuffindex .gt. 0) then
914     write(cunit) cbuffindex
915     write(cunit) k
916     write(cunit) (cbuff(ii), ii=1,cbuffindex)
917     endif
918    
919     #endif
920    
921     #ifdef ALLOW_SFLUX0_CONTROL
922    
923     il=ilnblnk( xx_sflux_file)
924     write(fname(1:80),'(80a)') ' '
925     write(fname(1:80),'(3a,i10.10)')
926     & yadmark,xx_sflux_file(1:il),'.',optimcycle
927     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
928     call MDSREADFIELD_2D_GL( "wsflux",
929     & prec, 'RL', 1,
930     & globfld2d,
931     & 1, mythid)
932     #endif
933     call MDSREADFIELD_2D_GL( fname,
934     & prec, 'RL', 1,
935     & globfld3d(1,1,1,1,1,1,1),
936     & 1, mythid)
937    
938     write(cunit) ncvarindex(4)
939     write(cunit) 1
940     write(cunit) 1
941     k = 1
942     cbuffindex = 0
943     do jp = 1,nPy
944     do bj = jtlo,jthi
945     do j = jmin,jmax
946     do ip = 1,nPx
947     do bi = itlo,ithi
948     do i = imin,imax
949     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
950     cbuffindex = cbuffindex + 1
951     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
952     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
953     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
954     #else
955     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
956     #endif
957     endif
958     enddo
959     enddo
960     enddo
961     enddo
962     enddo
963     enddo
964     c --> check cbuffindex.
965     if ( cbuffindex .gt. 0) then
966     write(cunit) cbuffindex
967     write(cunit) k
968     write(cunit) (cbuff(ii), ii=1,cbuffindex)
969     endif
970    
971     #endif
972    
973     #ifdef ALLOW_TAUU0_CONTROL
974    
975     il=ilnblnk( xx_tauu_file)
976     write(fname(1:80),'(80a)') ' '
977     write(fname(1:80),'(3a,i10.10)')
978     & yadmark,xx_tauu_file(1:il),'.',optimcycle
979     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
980     call MDSREADFIELD_2D_GL( "wtauu",
981     & prec, 'RL', 1,
982     & globfld2d,
983     & 1, mythid)
984     #endif
985     call MDSREADFIELD_2D_GL( fname,
986     & prec, 'RL', 1,
987     & globfld3d(1,1,1,1,1,1,1),
988     & 1, mythid)
989    
990     write(cunit) ncvarindex(5)
991     write(cunit) 1
992     write(cunit) 1
993     k = 1
994     cbuffindex = 0
995     do jp = 1,nPy
996     do bj = jtlo,jthi
997     do j = jmin,jmax
998     do ip = 1,nPx
999     do bi = itlo,ithi
1000     do i = imin,imax
1001     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
1002     cbuffindex = cbuffindex + 1
1003     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1004     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1005     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
1006     #else
1007     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1008     #endif
1009     endif
1010     enddo
1011     enddo
1012     enddo
1013     enddo
1014     enddo
1015     enddo
1016     c --> check cbuffindex.
1017     if ( cbuffindex .gt. 0) then
1018     write(cunit) cbuffindex
1019     write(cunit) k
1020     write(cunit) (cbuff(ii), ii=1,cbuffindex)
1021     endif
1022    
1023     #endif
1024    
1025     #ifdef ALLOW_TAUV0_CONTROL
1026    
1027     il=ilnblnk( xx_tauv_file)
1028     write(fname(1:80),'(80a)') ' '
1029     write(fname(1:80),'(3a,i10.10)')
1030     & yadmark,xx_tauv_file(1:il),'.',optimcycle
1031     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1032     call MDSREADFIELD_2D_GL( "wtauv",
1033     & prec, 'RL', 1,
1034     & globfld2d,
1035     & 1, mythid)
1036     #endif
1037     call MDSREADFIELD_2D_GL( fname,
1038     & prec, 'RL', 1,
1039     & globfld3d(1,1,1,1,1,1,1),
1040     & 1, mythid)
1041    
1042     write(cunit) ncvarindex(6)
1043     write(cunit) 1
1044     write(cunit) 1
1045     k = 1
1046     cbuffindex = 0
1047     do jp = 1,nPy
1048     do bj = jtlo,jthi
1049     do j = jmin,jmax
1050     do ip = 1,nPx
1051     do bi = itlo,ithi
1052     do i = imin,imax
1053     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
1054     cbuffindex = cbuffindex + 1
1055     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1056     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1057     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
1058     #else
1059     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1060     #endif
1061     endif
1062     enddo
1063     enddo
1064     enddo
1065     enddo
1066     enddo
1067     enddo
1068     c --> check cbuffindex.
1069     if ( cbuffindex .gt. 0) then
1070     write(cunit) cbuffindex
1071     write(cunit) k
1072     write(cunit) (cbuff(ii), ii=1,cbuffindex)
1073     endif
1074    
1075     #endif
1076    
1077     #ifdef ALLOW_SST0_CONTROL
1078    
1079     il=ilnblnk( xx_sst_file)
1080     write(fname(1:80),'(80a)') ' '
1081     write(fname(1:80),'(3a,i10.10)')
1082     & yadmark,xx_sst_file(1:il),'.',optimcycle
1083     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1084     call MDSREADFIELD_2D_GL( "wsst",
1085     & prec, 'RL', 1,
1086     & globfld2d,
1087     & 1, mythid)
1088     #endif
1089     call MDSREADFIELD_2D_GL( fname,
1090     & prec, 'RL', 1,
1091     & globfld3d(1,1,1,1,1,1,1),
1092     & 1, mythid)
1093    
1094     write(cunit) ncvarindex(7)
1095     write(cunit) 1
1096     write(cunit) 1
1097     k = 1
1098     cbuffindex = 0
1099     do jp = 1,nPy
1100     do bj = jtlo,jthi
1101     do j = jmin,jmax
1102     do ip = 1,nPx
1103     do bi = itlo,ithi
1104     do i = imin,imax
1105     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
1106     cbuffindex = cbuffindex + 1
1107     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1108     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1109     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
1110     #else
1111     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1112     #endif
1113     endif
1114     enddo
1115     enddo
1116     enddo
1117     enddo
1118     enddo
1119     enddo
1120     c --> check cbuffindex.
1121     if ( cbuffindex .gt. 0) then
1122     write(cunit) cbuffindex
1123     write(cunit) k
1124     write(cunit) (cbuff(ii), ii=1,cbuffindex)
1125     endif
1126    
1127     #endif
1128    
1129     #ifdef ALLOW_SSS0_CONTROL
1130    
1131     il=ilnblnk( xx_sss_file)
1132     write(fname(1:80),'(80a)') ' '
1133     write(fname(1:80),'(3a,i10.10)')
1134     & yadmark,xx_sss_file(1:il),'.',optimcycle
1135     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1136     call MDSREADFIELD_2D_GL( "wsss",
1137     & prec, 'RL', 1,
1138     & globfld2d,
1139     & 1, mythid)
1140     #endif
1141     call MDSREADFIELD_2D_GL( fname,
1142     & prec, 'RL', 1,
1143     & globfld3d(1,1,1,1,1,1,1),
1144     & 1, mythid)
1145    
1146     write(cunit) ncvarindex(8)
1147     write(cunit) 1
1148     write(cunit) 1
1149     k = 1
1150     cbuffindex = 0
1151     do jp = 1,nPy
1152     do bj = jtlo,jthi
1153     do j = jmin,jmax
1154     do ip = 1,nPx
1155     do bi = itlo,ithi
1156     do i = imin,imax
1157     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
1158     cbuffindex = cbuffindex + 1
1159     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1160     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1161     & * sqrt(globfld2d(i,bi,ip,j,bj,jp))
1162     #else
1163     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1164     #endif
1165     endif
1166     enddo
1167     enddo
1168     enddo
1169     enddo
1170     enddo
1171     enddo
1172     c --> check cbuffindex.
1173     if ( cbuffindex .gt. 0) then
1174     write(cunit) cbuffindex
1175     write(cunit) k
1176     write(cunit) (cbuff(ii), ii=1,cbuffindex)
1177     endif
1178    
1179     #endif
1180 heimbach 1.3
1181     #ifdef ALLOW_DIFFKR_CONTROL
1182    
1183     il=ilnblnk( xx_diffkr_file)
1184     write(fname(1:80),'(80a)') ' '
1185     write(fname(1:80),'(3a,i10.10)')
1186     & yadmark,xx_diffkr_file(1:il),'.',optimcycle
1187    
1188     call MDSREADFIELD_3D_GL( fname,
1189     & prec, 'RL', Nr,
1190     & globfld3d,
1191     & 1, mythid)
1192    
1193     write(cunit) ncvarindex(9)
1194     write(cunit) 1
1195     write(cunit) 1
1196     do k = 1,nr
1197     cbuffindex = 0
1198     do jp = 1,nPy
1199     do bj = jtlo,jthi
1200     do j = jmin,jmax
1201     do ip = 1,nPx
1202     do bi = itlo,ithi
1203     do i = imin,imax
1204     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
1205     cbuffindex = cbuffindex + 1
1206     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1207     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1208     cph & * sqrt(wdiffkr(k,bi,bj))
1209     #else
1210     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1211     #endif
1212     endif
1213     enddo
1214     enddo
1215     enddo
1216     enddo
1217     enddo
1218     enddo
1219     c --> check cbuffindex.
1220     if ( cbuffindex .gt. 0) then
1221     write(cunit) cbuffindex
1222     write(cunit) k
1223     write(cunit) (cbuff(ii), ii=1,cbuffindex)
1224     endif
1225     enddo
1226    
1227     #endif
1228    
1229     #ifdef ALLOW_KAPGM_CONTROL
1230    
1231     il=ilnblnk( xx_kapgm_file)
1232     write(fname(1:80),'(80a)') ' '
1233     write(fname(1:80),'(3a,i10.10)')
1234     & yadmark,xx_kapgm_file(1:il),'.',optimcycle
1235    
1236     call MDSREADFIELD_3D_GL( fname,
1237     & prec, 'RL', Nr,
1238     & globfld3d,
1239     & 1, mythid)
1240    
1241     write(cunit) ncvarindex(9)
1242     write(cunit) 1
1243     write(cunit) 1
1244     do k = 1,nr
1245     cbuffindex = 0
1246     do jp = 1,nPy
1247     do bj = jtlo,jthi
1248     do j = jmin,jmax
1249     do ip = 1,nPx
1250     do bi = itlo,ithi
1251     do i = imin,imax
1252     if (globmsk(i,bi,ip,j,bj,jp,k) .ne. 0. ) then
1253     cbuffindex = cbuffindex + 1
1254     #ifdef ALLOW_NONDIMENSIONAL_CONTROL_IO
1255     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1256     cph & * sqrt(wkapgm(k,bi,bj))
1257     #else
1258     cbuff(cbuffindex) = globfld3d(i,bi,ip,j,bj,jp,k)
1259     #endif
1260     endif
1261     enddo
1262     enddo
1263     enddo
1264     enddo
1265     enddo
1266     enddo
1267     c --> check cbuffindex.
1268     if ( cbuffindex .gt. 0) then
1269     write(cunit) cbuffindex
1270     write(cunit) k
1271     write(cunit) (cbuff(ii), ii=1,cbuffindex)
1272     endif
1273     enddo
1274    
1275     #endif
1276    
1277 heimbach 1.1
1278     close ( cunit )
1279    
1280     return
1281     end
1282    

  ViewVC Help
Powered by ViewVC 1.1.22