/[MITgcm]/MITgcm/pkg/grdchk/grdchk_getxx.F
ViewVC logotype

Annotation of /MITgcm/pkg/grdchk/grdchk_getxx.F

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


Revision 1.21 - (hide annotations) (download)
Thu Jan 17 20:49:27 2008 UTC (16 years, 4 months ago) by dfer
Branch: MAIN
Changes since 1.20: +22 -1 lines
More bits for tutorial_global_oce_optim.

1 dfer 1.21 C $Header: /u/gcmpack/MITgcm/pkg/grdchk/grdchk_getxx.F,v 1.20 2007/10/09 00:05:45 jmc Exp $
2 jmc 1.20 C $Name: $
3 heimbach 1.2
4     #include "CTRL_CPPOPTIONS.h"
5    
6    
7     subroutine grdchk_getxx(
8     I icvrec,
9 heimbach 1.5 I theSimulationMode,
10 heimbach 1.2 I itile,
11     I jtile,
12     I layer,
13     I itilepos,
14     I jtilepos,
15     I xx_comp_ref,
16     I xx_comp_pert,
17 heimbach 1.5 I localEps,
18 heimbach 1.2 I mythid
19     & )
20    
21     c ==================================================================
22     c SUBROUTINE grdchk_getxx
23     c ==================================================================
24     c
25     c o Set component a component of the control vector; xx(loc)
26     c
27     c started: Christian Eckert eckert@mit.edu 08-Mar-2000
28     c continued: heimbach@mit.edu: 13-Jun-2001
29     c
30     c ==================================================================
31     c SUBROUTINE grdchk_getxx
32     c ==================================================================
33    
34     implicit none
35    
36     c == global variables ==
37    
38     #include "EEPARAMS.h"
39     #include "SIZE.h"
40     #include "ctrl.h"
41     #include "grdchk.h"
42     #include "optim.h"
43    
44     c == routine arguments ==
45    
46     integer icvrec
47 heimbach 1.5 integer theSimulationMode
48 heimbach 1.2 integer jtile
49     integer itile
50     integer layer
51     integer itilepos
52     integer jtilepos
53     _RL xx_comp_ref
54     _RL xx_comp_pert
55 heimbach 1.5 _RL localEps
56 heimbach 1.2 integer mythid
57    
58 heimbach 1.10 #ifdef ALLOW_GRDCHK
59 heimbach 1.2 c == local variables ==
60    
61     integer il
62     integer dumiter
63     _RL dumtime
64     _RL dummy
65    
66     logical doglobalread
67     logical ladinit
68    
69     character*(80) fname
70    
71     c-- == external ==
72    
73     integer ilnblnk
74     external ilnblnk
75    
76     c-- == end of interface ==
77    
78     doglobalread = .false.
79     ladinit = .false.
80     dumiter = 0
81     dumtime = 0. _d 0
82 heimbach 1.7 write(fname(1:80),'(80a)') ' '
83 heimbach 1.2
84 heimbach 1.4 if ( grdchkvarindex .eq. 0 ) then
85     STOP 'GRDCHK INDEX 0 NOT ALLOWED'
86    
87 heimbach 1.2 #ifdef ALLOW_THETA0_CONTROL
88 heimbach 1.4 else if ( grdchkvarindex .eq. 1 ) then
89 heimbach 1.2 il=ilnblnk( xx_theta_file )
90 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
91     write(fname(1:80),'(3a,i10.10)')
92 heimbach 1.7 & yadmark, xx_theta_file(1:il),'.',optimcycle
93 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
94     write(fname(1:80),'(2a,i10.10)')
95     & xx_theta_file(1:il),'.',optimcycle
96     end if
97 heimbach 1.18 call active_read_xyz( fname, tmpfld3d, 1,
98 heimbach 1.2 & doglobalread, ladinit, optimcycle,
99     & mythid, dummy)
100     xx_comp_ref = tmpfld3d( itilepos,jtilepos,layer,itile,jtile )
101 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
102 heimbach 1.2 tmpfld3d( itilepos,jtilepos,layer,itile,jtile ) = xx_comp_pert
103 heimbach 1.18 call active_write_xyz( fname, tmpfld3d, 1,
104 heimbach 1.2 & optimcycle,
105     & mythid, dummy)
106     #endif /* ALLOW_THETA0_CONTROL */
107    
108     #ifdef ALLOW_SALT0_CONTROL
109     else if ( grdchkvarindex .eq. 2 ) then
110     il=ilnblnk( xx_salt_file )
111 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
112     write(fname(1:80),'(3a,i10.10)')
113 heimbach 1.7 & yadmark, xx_salt_file(1:il),'.',optimcycle
114 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
115     write(fname(1:80),'(2a,i10.10)')
116     & xx_salt_file(1:il),'.',optimcycle
117     end if
118 heimbach 1.18 call active_read_xyz( fname, tmpfld3d, 1,
119 heimbach 1.2 & doglobalread, ladinit, optimcycle,
120     & mythid, dummy)
121     xx_comp_ref = tmpfld3d( itilepos,jtilepos,layer,itile,jtile )
122 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
123 heimbach 1.2 tmpfld3d( itilepos,jtilepos,layer,itile,jtile ) = xx_comp_pert
124 heimbach 1.18 call active_write_xyz( fname, tmpfld3d, 1,
125 heimbach 1.2 & optimcycle,
126     & mythid, dummy)
127     #endif /* ALLOW_SALT0_CONTROL */
128    
129     #ifdef ALLOW_HFLUX_CONTROL
130     else if ( grdchkvarindex .eq. 3 ) then
131     il=ilnblnk( xx_hflux_file )
132 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
133     write(fname(1:80),'(3a,i10.10)')
134 heimbach 1.7 & yadmark, xx_hflux_file(1:il),'.',optimcycle
135 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
136     write(fname(1:80),'(2a,i10.10)')
137     & xx_hflux_file(1:il),'.',optimcycle
138     end if
139 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
140 heimbach 1.2 & doglobalread, ladinit, optimcycle,
141     & mythid, dummy)
142     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
143 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
144 heimbach 1.2 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
145 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
146 heimbach 1.2 & optimcycle,
147     & mythid, dummy)
148     #endif /* ALLOW_HFLUX_CONTROL */
149    
150     #ifdef ALLOW_SFLUX_CONTROL
151     else if ( grdchkvarindex .eq. 4 ) then
152     il=ilnblnk( xx_sflux_file )
153 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
154     write(fname(1:80),'(3a,i10.10)')
155 heimbach 1.7 & yadmark, xx_sflux_file(1:il),'.',optimcycle
156 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
157     write(fname(1:80),'(2a,i10.10)')
158     & xx_sflux_file(1:il),'.',optimcycle
159     end if
160 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
161 heimbach 1.2 & doglobalread, ladinit, optimcycle,
162     & mythid, dummy)
163     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
164 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
165 heimbach 1.2 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
166 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
167 heimbach 1.2 & optimcycle,
168     & mythid, dummy)
169     #endif /* ALLOW_SFLUX_CONTROL */
170    
171     #ifdef ALLOW_USTRESS_CONTROL
172     else if ( grdchkvarindex .eq. 5 ) then
173     il=ilnblnk( xx_tauu_file )
174 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
175     write(fname(1:80),'(3a,i10.10)')
176 heimbach 1.7 & yadmark, xx_tauu_file(1:il),'.',optimcycle
177 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
178     write(fname(1:80),'(2a,i10.10)')
179     & xx_tauu_file(1:il),'.',optimcycle
180     end if
181 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
182 heimbach 1.2 & doglobalread, ladinit, optimcycle,
183     & mythid, dummy)
184     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
185 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
186 heimbach 1.2 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
187 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
188 heimbach 1.2 & optimcycle,
189     & mythid, dummy)
190     #endif /* ALLOW_USTRESS_CONTROL */
191    
192     #ifdef ALLOW_VSTRESS_CONTROL
193     else if ( grdchkvarindex .eq. 6 ) then
194     il=ilnblnk( xx_tauv_file )
195 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
196     write(fname(1:80),'(3a,i10.10)')
197 heimbach 1.7 & yadmark, xx_tauv_file(1:il),'.',optimcycle
198 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
199     write(fname(1:80),'(2a,i10.10)')
200     & xx_tauv_file(1:il),'.',optimcycle
201     end if
202 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
203 heimbach 1.2 & doglobalread, ladinit, optimcycle,
204     & mythid, dummy)
205     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
206 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
207 heimbach 1.2 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
208 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
209 heimbach 1.2 & optimcycle,
210     & mythid, dummy)
211     #endif /* ALLOW_VSTRESS_CONTROL */
212    
213 heimbach 1.7 #ifdef ALLOW_ATEMP_CONTROL
214     else if ( grdchkvarindex .eq. 7 ) then
215     il=ilnblnk( xx_atemp_file )
216     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
217     write(fname(1:80),'(3a,i10.10)')
218     & yadmark, xx_atemp_file(1:il),'.',optimcycle
219     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
220     write(fname(1:80),'(2a,i10.10)')
221     & xx_atemp_file(1:il),'.',optimcycle
222     end if
223 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
224 heimbach 1.7 & doglobalread, ladinit, optimcycle,
225     & mythid, dummy)
226     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
227     xx_comp_pert = xx_comp_ref + localEps
228     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
229 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
230 heimbach 1.7 & optimcycle,
231     & mythid, dummy)
232     #endif /* ALLOW_ATEMP_CONTROL */
233    
234     #ifdef ALLOW_AQH_CONTROL
235     else if ( grdchkvarindex .eq. 8 ) then
236     il=ilnblnk( xx_aqh_file )
237     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
238     write(fname(1:80),'(3a,i10.10)')
239     & yadmark, xx_aqh_file(1:il),'.',optimcycle
240     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
241     write(fname(1:80),'(2a,i10.10)')
242     & xx_aqh_file(1:il),'.',optimcycle
243     end if
244 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
245 heimbach 1.7 & doglobalread, ladinit, optimcycle,
246     & mythid, dummy)
247     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
248     xx_comp_pert = xx_comp_ref + localEps
249     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
250 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
251 heimbach 1.7 & optimcycle,
252     & mythid, dummy)
253     #endif /* ALLOW_AQH_CONTROL */
254    
255     #ifdef ALLOW_UWIND_CONTROL
256     else if ( grdchkvarindex .eq. 9 ) then
257     il=ilnblnk( xx_uwind_file )
258     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
259     write(fname(1:80),'(3a,i10.10)')
260     & yadmark, xx_uwind_file(1:il),'.',optimcycle
261     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
262     write(fname(1:80),'(2a,i10.10)')
263     & xx_uwind_file(1:il),'.',optimcycle
264     end if
265 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
266 heimbach 1.7 & doglobalread, ladinit, optimcycle,
267     & mythid, dummy)
268     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
269     xx_comp_pert = xx_comp_ref + localEps
270     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
271 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
272 heimbach 1.7 & optimcycle,
273     & mythid, dummy)
274     #endif /* ALLOW_UWIND_CONTROL */
275    
276     #ifdef ALLOW_VWIND_CONTROL
277     else if ( grdchkvarindex .eq. 10 ) then
278     il=ilnblnk( xx_vwind_file )
279     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
280     write(fname(1:80),'(3a,i10.10)')
281     & yadmark, xx_vwind_file(1:il),'.',optimcycle
282     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
283     write(fname(1:80),'(2a,i10.10)')
284     & xx_vwind_file(1:il),'.',optimcycle
285     end if
286 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
287 heimbach 1.7 & doglobalread, ladinit, optimcycle,
288     & mythid, dummy)
289     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
290     xx_comp_pert = xx_comp_ref + localEps
291     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
292 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
293 heimbach 1.7 & optimcycle,
294     & mythid, dummy)
295     #endif /* ALLOW_VWIND_CONTROL */
296 heimbach 1.8
297     #ifdef ALLOW_OBCSN_CONTROL
298     else if ( grdchkvarindex .eq. 11 ) then
299     il=ilnblnk( xx_obcsn_file )
300     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
301     write(fname(1:80),'(3a,i10.10)')
302     & yadmark, xx_obcsn_file(1:il),'.',optimcycle
303     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
304     write(fname(1:80),'(2a,i10.10)')
305     & xx_obcsn_file(1:il),'.',optimcycle
306     end if
307    
308 heimbach 1.18 call active_read_xz( fname, tmpfldxz, icvrec,
309 heimbach 1.8 & doglobalread, ladinit, optimcycle,
310     & mythid, dummy)
311    
312     xx_comp_ref = tmpfldxz( itilepos,layer,itile,jtile )
313     xx_comp_pert = xx_comp_ref + localEps
314     tmpfldxz( itilepos,layer,itile,jtile ) = xx_comp_pert
315    
316 heimbach 1.18 call active_write_xz( fname, tmpfldxz, icvrec,
317 heimbach 1.8 & optimcycle,
318     & mythid, dummy)
319    
320     #endif /* ALLOW_OBCSN_CONTROL */
321    
322     #ifdef ALLOW_OBCSS_CONTROL
323     else if ( grdchkvarindex .eq. 12 ) then
324     il=ilnblnk( xx_obcss_file )
325     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
326     write(fname(1:80),'(3a,i10.10)')
327     & yadmark, xx_obcss_file(1:il),'.',optimcycle
328     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
329     write(fname(1:80),'(2a,i10.10)')
330     & xx_obcss_file(1:il),'.',optimcycle
331     end if
332    
333 heimbach 1.18 call active_read_xz( fname, tmpfldxz, icvrec,
334 heimbach 1.8 & doglobalread, ladinit, optimcycle,
335     & mythid, dummy)
336    
337     xx_comp_ref = tmpfldxz( itilepos,layer,itile,jtile )
338     xx_comp_pert = xx_comp_ref + localEps
339     tmpfldxz( itilepos,layer,itile,jtile ) = xx_comp_pert
340    
341 heimbach 1.18 call active_write_xz( fname, tmpfldxz, icvrec,
342 heimbach 1.8 & optimcycle,
343     & mythid, dummy)
344    
345     #endif /* ALLOW_OBCSS_CONTROL */
346    
347     #ifdef ALLOW_OBCSW_CONTROL
348     else if ( grdchkvarindex .eq. 13 ) then
349     il=ilnblnk( xx_obcsw_file )
350     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
351     write(fname(1:80),'(3a,i10.10)')
352     & yadmark, xx_obcsw_file(1:il),'.',optimcycle
353     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
354     write(fname(1:80),'(2a,i10.10)')
355     & xx_obcsw_file(1:il),'.',optimcycle
356     end if
357    
358 heimbach 1.18 call active_read_yz( fname, tmpfldyz, icvrec,
359 heimbach 1.8 & doglobalread, ladinit, optimcycle,
360     & mythid, dummy)
361    
362     xx_comp_ref = tmpfldyz( jtilepos,layer,itile,jtile )
363     xx_comp_pert = xx_comp_ref + localEps
364     tmpfldyz( jtilepos,layer,itile,jtile ) = xx_comp_pert
365    
366 heimbach 1.18 call active_write_yz( fname, tmpfldyz, icvrec,
367 heimbach 1.8 & optimcycle,
368     & mythid, dummy)
369    
370     #endif /* ALLOW_OBCSW_CONTROL */
371    
372     #ifdef ALLOW_OBCSE_CONTROL
373     else if ( grdchkvarindex .eq. 14 ) then
374     il=ilnblnk( xx_obcse_file )
375     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
376     write(fname(1:80),'(3a,i10.10)')
377     & yadmark, xx_obcse_file(1:il),'.',optimcycle
378     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
379     write(fname(1:80),'(2a,i10.10)')
380     & xx_obcse_file(1:il),'.',optimcycle
381     end if
382    
383 heimbach 1.18 call active_read_yz( fname, tmpfldyz, icvrec,
384 heimbach 1.8 & doglobalread, ladinit, optimcycle,
385     & mythid, dummy)
386    
387     xx_comp_ref = tmpfldyz( jtilepos,layer,itile,jtile )
388     xx_comp_pert = xx_comp_ref + localEps
389     tmpfldyz( jtilepos,layer,itile,jtile ) = xx_comp_pert
390    
391 heimbach 1.18 call active_write_yz( fname, tmpfldyz, icvrec,
392 heimbach 1.8 & optimcycle,
393     & mythid, dummy)
394    
395     #endif /* ALLOW_OBCSE_CONTROL */
396 heimbach 1.7
397 heimbach 1.15 #ifdef ALLOW_DIFFKR_CONTROL
398     else if ( grdchkvarindex .eq. 15 ) then
399     il=ilnblnk( xx_diffkr_file )
400     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
401     write(fname(1:80),'(3a,i10.10)')
402     & yadmark, xx_diffkr_file(1:il),'.',optimcycle
403     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
404     write(fname(1:80),'(2a,i10.10)')
405     & xx_diffkr_file(1:il),'.',optimcycle
406     end if
407    
408 heimbach 1.18 call active_read_xyz( fname, tmpfld3d, 1,
409 heimbach 1.15 & doglobalread, ladinit, optimcycle,
410     & mythid, dummy)
411    
412     xx_comp_ref = tmpfld3d( itilepos,jtilepos,layer,itile,jtile )
413     xx_comp_pert = xx_comp_ref + localEps
414     tmpfld3d( itilepos,jtilepos,layer,itile,jtile ) = xx_comp_pert
415    
416 heimbach 1.18 call active_write_xyz( fname, tmpfld3d, 1,
417 heimbach 1.15 & optimcycle,
418     & mythid, dummy)
419    
420     #endif /* ALLOW_DIFFKR_CONTROL */
421    
422     #ifdef ALLOW_KAPGM_CONTROL
423     else if ( grdchkvarindex .eq. 16 ) then
424     il=ilnblnk( xx_kapgm_file )
425     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
426     write(fname(1:80),'(3a,i10.10)')
427     & yadmark, xx_kapgm_file(1:il),'.',optimcycle
428     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
429     write(fname(1:80),'(2a,i10.10)')
430     & xx_kapgm_file(1:il),'.',optimcycle
431     end if
432    
433 heimbach 1.18 call active_read_xyz( fname, tmpfld3d, 1,
434 heimbach 1.15 & doglobalread, ladinit, optimcycle,
435     & mythid, dummy)
436    
437     xx_comp_ref = tmpfld3d( itilepos,jtilepos,layer,itile,jtile )
438     xx_comp_pert = xx_comp_ref + localEps
439     tmpfld3d( itilepos,jtilepos,layer,itile,jtile ) = xx_comp_pert
440    
441 heimbach 1.18 call active_write_xyz( fname, tmpfld3d, 1,
442 heimbach 1.15 & optimcycle,
443     & mythid, dummy)
444    
445     #endif /* ALLOW_KAPGM_CONTROL */
446    
447 heimbach 1.12 #ifdef ALLOW_TR10_CONTROL
448 heimbach 1.2 else if ( grdchkvarindex .eq. 17 ) then
449 heimbach 1.12 il=ilnblnk( xx_tr1_file )
450 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
451     write(fname(1:80),'(3a,i10.10)')
452 heimbach 1.12 & yadmark, xx_tr1_file(1:il),'.',optimcycle
453 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
454     write(fname(1:80),'(2a,i10.10)')
455 heimbach 1.12 & xx_tr1_file(1:il),'.',optimcycle
456 heimbach 1.5 end if
457 heimbach 1.2
458 heimbach 1.18 call active_read_xyz( fname, tmpfld3d, icvrec,
459 heimbach 1.2 & doglobalread, ladinit, optimcycle,
460     & mythid, dummy)
461    
462 heimbach 1.12 xx_comp_ref = tmpfld3d( itilepos,jtilepos,layer,itile,jtile )
463 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
464 heimbach 1.12 tmpfld3d( itilepos,jtilepos,layer,itile,jtile ) = xx_comp_pert
465 heimbach 1.2
466 heimbach 1.18 call active_write_xyz( fname, tmpfld3d, icvrec,
467 heimbach 1.2 & optimcycle,
468     & mythid, dummy)
469    
470 heimbach 1.12 #endif /* ALLOW_TR10_CONTROL */
471 heimbach 1.2
472 heimbach 1.14 #if (defined (ALLOW_SST_CONTROL) || defined (ALLOW_SST0_CONTROL))
473 heimbach 1.2 else if ( grdchkvarindex .eq. 18 ) then
474     il=ilnblnk( xx_sst_file )
475 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
476     write(fname(1:80),'(3a,i10.10)')
477 heimbach 1.7 & yadmark, xx_sst_file(1:il),'.',optimcycle
478 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
479     write(fname(1:80),'(2a,i10.10)')
480     & xx_sst_file(1:il),'.',optimcycle
481     end if
482 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
483 heimbach 1.2 & doglobalread, ladinit, optimcycle,
484     & mythid, dummy)
485     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
486 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
487 heimbach 1.2 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
488 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
489 heimbach 1.2 & optimcycle,
490     & mythid, dummy)
491     #endif /* ALLOW_SST0_CONTROL */
492    
493 heimbach 1.14 #if (defined (ALLOW_SSS_CONTROL) || defined (ALLOW_SSS0_CONTROL))
494 heimbach 1.2 else if ( grdchkvarindex .eq. 19 ) then
495     il=ilnblnk( xx_sss_file )
496 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
497     write(fname(1:80),'(3a,i10.10)')
498 heimbach 1.7 & yadmark, xx_sss_file(1:il),'.',optimcycle
499 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
500     write(fname(1:80),'(2a,i10.10)')
501     & xx_sss_file(1:il),'.',optimcycle
502     end if
503 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
504 heimbach 1.2 & doglobalread, ladinit, optimcycle,
505     & mythid, dummy)
506     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
507 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
508 heimbach 1.2 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
509 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
510 heimbach 1.2 & optimcycle,
511     & mythid, dummy)
512     #endif /* ALLOW_SSS0_CONTROL */
513    
514 heimbach 1.16 #ifdef ALLOW_DEPTH_CONTROL
515 heimbach 1.3 else if ( grdchkvarindex .eq. 20 ) then
516 heimbach 1.16 il=ilnblnk( xx_depth_file )
517 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
518     write(fname(1:80),'(3a,i10.10)')
519 heimbach 1.16 & yadmark, xx_depth_file(1:il),'.',optimcycle
520 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
521     write(fname(1:80),'(2a,i10.10)')
522 heimbach 1.16 & xx_depth_file(1:il),'.',optimcycle
523 heimbach 1.5 end if
524 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
525 heimbach 1.3 & doglobalread, ladinit, optimcycle,
526     & mythid, dummy)
527     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
528 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
529 heimbach 1.3 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
530 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
531 heimbach 1.3 & optimcycle,
532     & mythid, dummy)
533 heimbach 1.16 #endif /* ALLOW_DEPTH_CONTROL */
534 heimbach 1.4
535     #ifdef ALLOW_EFLUXY0_CONTROL
536     else if ( grdchkvarindex .eq. 21 ) then
537     il=ilnblnk( xx_efluxy_file )
538     write(fname(1:80),'(80a)') ' '
539 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
540     write(fname(1:80),'(3a,i10.10)')
541 heimbach 1.7 & yadmark, xx_efluxy_file(1:il),'.',optimcycle
542 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
543     write(fname(1:80),'(2a,i10.10)')
544     & xx_efluxy_file(1:il),'.',optimcycle
545     end if
546 heimbach 1.4
547 heimbach 1.18 call active_read_xyz( fname, tmpfld3d, 1,
548 heimbach 1.4 & doglobalread, ladinit, optimcycle,
549     & mythid, dummy)
550    
551     xx_comp_ref = tmpfld3d( itilepos,jtilepos,layer,itile,jtile )
552 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
553 heimbach 1.4 tmpfld3d( itilepos,jtilepos,layer,itile,jtile ) = xx_comp_pert
554    
555 heimbach 1.18 call active_write_xyz( fname, tmpfld3d, 1,
556 heimbach 1.4 & optimcycle,
557     & mythid, dummy)
558    
559     #endif /* ALLOW_EFLUXY0_CONTROL */
560    
561     #ifdef ALLOW_EFLUXP0_CONTROL
562     else if ( grdchkvarindex .eq. 22 ) then
563     il=ilnblnk( xx_efluxp_file )
564     write(fname(1:80),'(80a)') ' '
565 heimbach 1.5 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
566     write(fname(1:80),'(3a,i10.10)')
567 heimbach 1.7 & yadmark, xx_efluxp_file(1:il),'.',optimcycle
568 heimbach 1.5 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
569     write(fname(1:80),'(2a,i10.10)')
570     & xx_efluxp_file(1:il),'.',optimcycle
571     end if
572 heimbach 1.4
573 heimbach 1.18 call active_read_xyz( fname, tmpfld3d, 1,
574 heimbach 1.4 & doglobalread, ladinit, optimcycle,
575     & mythid, dummy)
576    
577     xx_comp_ref = tmpfld3d( itilepos,jtilepos,layer,itile,jtile )
578 heimbach 1.5 xx_comp_pert = xx_comp_ref + localEps
579 heimbach 1.4 tmpfld3d( itilepos,jtilepos,layer,itile,jtile ) = xx_comp_pert
580    
581 heimbach 1.18 call active_write_xyz( fname, tmpfld3d, 1,
582 heimbach 1.4 & optimcycle,
583     & mythid, dummy)
584    
585     #endif /* ALLOW_EFLUXP0_CONTROL */
586    
587 dfer 1.21 #ifdef ALLOW_HFLUXM_CONTROL
588     else if ( grdchkvarindex .eq. 24 ) then
589     il=ilnblnk( xx_hfluxm_file )
590     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
591     write(fname(1:80),'(3a,i10.10)')
592     & yadmark, xx_hfluxm_file(1:il),'.',optimcycle
593     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
594     write(fname(1:80),'(2a,i10.10)')
595     & xx_hfluxm_file(1:il),'.',optimcycle
596     end if
597     call active_read_xy( fname, tmpfld2d, icvrec,
598     & doglobalread, ladinit, optimcycle,
599     & mythid, dummy)
600     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
601     xx_comp_pert = xx_comp_ref + localEps
602     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
603     call active_write_xy( fname, tmpfld2d, icvrec,
604     & optimcycle,
605     & mythid, dummy)
606     #endif /* ALLOW_HFLUXM_CONTROL */
607    
608 heimbach 1.12 #ifdef ALLOW_PRECIP_CONTROL
609 heimbach 1.11 else if ( grdchkvarindex .eq. 32 ) then
610 heimbach 1.12 il=ilnblnk( xx_precip_file )
611     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
612     write(fname(1:80),'(3a,i10.10)')
613     & yadmark, xx_precip_file(1:il),'.',optimcycle
614     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
615     write(fname(1:80),'(2a,i10.10)')
616     & xx_precip_file(1:il),'.',optimcycle
617     end if
618 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
619 heimbach 1.12 & doglobalread, ladinit, optimcycle,
620     & mythid, dummy)
621     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
622     xx_comp_pert = xx_comp_ref + localEps
623     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
624 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
625 heimbach 1.12 & optimcycle,
626     & mythid, dummy)
627     #endif /* ALLOW_PRECIP_CONTROL */
628    
629     #ifdef ALLOW_SWFLUX_CONTROL
630     else if ( grdchkvarindex .eq. 33 ) then
631     il=ilnblnk( xx_swflux_file )
632 heimbach 1.11 if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
633     write(fname(1:80),'(3a,i10.10)')
634 heimbach 1.12 & yadmark, xx_swflux_file(1:il),'.',optimcycle
635 heimbach 1.11 else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
636     write(fname(1:80),'(2a,i10.10)')
637 heimbach 1.12 & xx_swflux_file(1:il),'.',optimcycle
638 heimbach 1.11 end if
639 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
640 heimbach 1.11 & doglobalread, ladinit, optimcycle,
641     & mythid, dummy)
642 heimbach 1.12 xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
643 heimbach 1.11 xx_comp_pert = xx_comp_ref + localEps
644 heimbach 1.12 tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
645 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
646 heimbach 1.11 & optimcycle,
647     & mythid, dummy)
648 heimbach 1.12 #endif /* ALLOW_SWFLUX_CONTROL */
649 heimbach 1.11
650 heimbach 1.13 #ifdef ALLOW_SWDOWN_CONTROL
651     else if ( grdchkvarindex .eq. 34 ) then
652     il=ilnblnk( xx_swdown_file )
653     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
654     write(fname(1:80),'(3a,i10.10)')
655     & yadmark, xx_swdown_file(1:il),'.',optimcycle
656     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
657     write(fname(1:80),'(2a,i10.10)')
658     & xx_swdown_file(1:il),'.',optimcycle
659     end if
660 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
661 heimbach 1.17 & doglobalread, ladinit, optimcycle,
662     & mythid, dummy)
663     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
664     xx_comp_pert = xx_comp_ref + localEps
665     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
666 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
667 heimbach 1.17 & optimcycle,
668     & mythid, dummy)
669     #endif /* ALLOW_SWDOWN_CONTROL */
670 heimbach 1.13
671 heimbach 1.17 #ifdef ALLOW_LWFLUX_CONTROL
672     else if ( grdchkvarindex .eq. 35 ) then
673     il=ilnblnk( xx_lwflux_file )
674     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
675     write(fname(1:80),'(3a,i10.10)')
676     & yadmark, xx_lwflux_file(1:il),'.',optimcycle
677     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
678     write(fname(1:80),'(2a,i10.10)')
679     & xx_lwflux_file(1:il),'.',optimcycle
680     end if
681 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
682 heimbach 1.13 & doglobalread, ladinit, optimcycle,
683     & mythid, dummy)
684 heimbach 1.17 xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
685     xx_comp_pert = xx_comp_ref + localEps
686     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
687 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
688 heimbach 1.17 & optimcycle,
689     & mythid, dummy)
690     #endif /* ALLOW_LWFLUX_CONTROL */
691 heimbach 1.13
692 heimbach 1.17 #ifdef ALLOW_LWDOWN_CONTROL
693     else if ( grdchkvarindex .eq. 36 ) then
694     il=ilnblnk( xx_lwdown_file )
695     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
696     write(fname(1:80),'(3a,i10.10)')
697     & yadmark, xx_lwdown_file(1:il),'.',optimcycle
698     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
699     write(fname(1:80),'(2a,i10.10)')
700     & xx_lwdown_file(1:il),'.',optimcycle
701     end if
702 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
703 heimbach 1.17 & doglobalread, ladinit, optimcycle,
704     & mythid, dummy)
705 heimbach 1.13 xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
706     xx_comp_pert = xx_comp_ref + localEps
707     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
708 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
709 heimbach 1.17 & optimcycle,
710     & mythid, dummy)
711     #endif /* ALLOW_LWDOWN_CONTROL */
712 heimbach 1.13
713 heimbach 1.17 #ifdef ALLOW_EVAP_CONTROL
714     else if ( grdchkvarindex .eq. 37 ) then
715     il=ilnblnk( xx_evap_file )
716     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
717     write(fname(1:80),'(3a,i10.10)')
718     & yadmark, xx_evap_file(1:il),'.',optimcycle
719     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
720     write(fname(1:80),'(2a,i10.10)')
721     & xx_evap_file(1:il),'.',optimcycle
722     end if
723 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
724 heimbach 1.17 & doglobalread, ladinit, optimcycle,
725     & mythid, dummy)
726     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
727     xx_comp_pert = xx_comp_ref + localEps
728     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
729 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
730 heimbach 1.13 & optimcycle,
731     & mythid, dummy)
732 heimbach 1.17 #endif /* ALLOW_EVAP_CONTROL */
733 heimbach 1.13
734 heimbach 1.17 #ifdef ALLOW_SNOWPRECIP_CONTROL
735     else if ( grdchkvarindex .eq. 38 ) then
736     il=ilnblnk( xx_snowprecip_file )
737     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
738     write(fname(1:80),'(3a,i10.10)')
739     & yadmark, xx_snowprecip_file(1:il),'.',optimcycle
740     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
741     write(fname(1:80),'(2a,i10.10)')
742     & xx_snowprecip_file(1:il),'.',optimcycle
743     end if
744 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
745 heimbach 1.17 & doglobalread, ladinit, optimcycle,
746     & mythid, dummy)
747     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
748     xx_comp_pert = xx_comp_ref + localEps
749     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
750 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
751 heimbach 1.17 & optimcycle,
752     & mythid, dummy)
753     #endif /* ALLOW_SNOWPRECIP_CONTROL */
754    
755     #ifdef ALLOW_APRESSURE_CONTROL
756     else if ( grdchkvarindex .eq. 39 ) then
757     il=ilnblnk( xx_apressure_file )
758     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
759     write(fname(1:80),'(3a,i10.10)')
760     & yadmark, xx_apressure_file(1:il),'.',optimcycle
761     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
762     write(fname(1:80),'(2a,i10.10)')
763     & xx_apressure_file(1:il),'.',optimcycle
764     end if
765 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
766 heimbach 1.17 & doglobalread, ladinit, optimcycle,
767     & mythid, dummy)
768     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
769     xx_comp_pert = xx_comp_ref + localEps
770     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
771 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
772 heimbach 1.17 & optimcycle,
773     & mythid, dummy)
774     #endif /* ALLOW_APRESSURE_CONTROL */
775    
776     #ifdef ALLOW_RUNOFF_CONTROL
777     else if ( grdchkvarindex .eq. 40 ) then
778     il=ilnblnk( xx_runoff_file )
779     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
780     write(fname(1:80),'(3a,i10.10)')
781     & yadmark, xx_runoff_file(1:il),'.',optimcycle
782     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
783     write(fname(1:80),'(2a,i10.10)')
784     & xx_runoff_file(1:il),'.',optimcycle
785     end if
786 heimbach 1.18 call active_read_xy( fname, tmpfld2d, icvrec,
787 heimbach 1.17 & doglobalread, ladinit, optimcycle,
788     & mythid, dummy)
789     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
790     xx_comp_pert = xx_comp_ref + localEps
791     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
792 heimbach 1.18 call active_write_xy( fname, tmpfld2d, icvrec,
793 heimbach 1.17 & optimcycle,
794     & mythid, dummy)
795     #endif /* ALLOW_RUNOFF_CONTROL */
796 heimbach 1.13
797 heimbach 1.19 #ifdef ALLOW_SIAREA_CONTROL
798     else if ( grdchkvarindex .eq. 41 ) then
799     il=ilnblnk( xx_siarea_file )
800     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
801     write(fname(1:80),'(3a,i10.10)')
802     & yadmark, xx_siarea_file(1:il),'.',optimcycle
803     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
804     write(fname(1:80),'(2a,i10.10)')
805     & xx_siarea_file(1:il),'.',optimcycle
806     end if
807     call active_read_xy( fname, tmpfld2d, icvrec,
808     & doglobalread, ladinit, optimcycle,
809     & mythid, dummy)
810     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
811     xx_comp_pert = xx_comp_ref + localEps
812     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
813     call active_write_xy( fname, tmpfld2d, icvrec,
814     & optimcycle,
815     & mythid, dummy)
816     #endif /* ALLOW_SIAREA_CONTROL */
817    
818     #ifdef ALLOW_SIHEFF_CONTROL
819     else if ( grdchkvarindex .eq. 42 ) then
820     il=ilnblnk( xx_siheff_file )
821     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
822     write(fname(1:80),'(3a,i10.10)')
823     & yadmark, xx_siheff_file(1:il),'.',optimcycle
824     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
825     write(fname(1:80),'(2a,i10.10)')
826     & xx_siheff_file(1:il),'.',optimcycle
827     end if
828     call active_read_xy( fname, tmpfld2d, icvrec,
829     & doglobalread, ladinit, optimcycle,
830     & mythid, dummy)
831     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
832     xx_comp_pert = xx_comp_ref + localEps
833     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
834     call active_write_xy( fname, tmpfld2d, icvrec,
835     & optimcycle,
836     & mythid, dummy)
837     #endif /* ALLOW_SIHEFF_CONTROL */
838    
839     #ifdef ALLOW_SIHSNOW_CONTROL
840     else if ( grdchkvarindex .eq. 43 ) then
841     il=ilnblnk( xx_sihsnow_file )
842     if ( theSimulationMode .EQ. TANGENT_SIMULATION ) then
843     write(fname(1:80),'(3a,i10.10)')
844     & yadmark, xx_sihsnow_file(1:il),'.',optimcycle
845     else if ( theSimulationMode .EQ. FORWARD_SIMULATION ) then
846     write(fname(1:80),'(2a,i10.10)')
847     & xx_sihsnow_file(1:il),'.',optimcycle
848     end if
849     call active_read_xy( fname, tmpfld2d, icvrec,
850     & doglobalread, ladinit, optimcycle,
851     & mythid, dummy)
852     xx_comp_ref = tmpfld2d( itilepos,jtilepos,itile,jtile )
853     xx_comp_pert = xx_comp_ref + localEps
854     tmpfld2d( itilepos,jtilepos,itile,jtile ) = xx_comp_pert
855     call active_write_xy( fname, tmpfld2d, icvrec,
856     & optimcycle,
857     & mythid, dummy)
858     #endif /* ALLOW_SIHSNOW_CONTROL */
859    
860 heimbach 1.2 else
861     ce --> this index does not exist yet.
862     endif
863    
864 heimbach 1.10 #endif /* ALLOW_GRDCHK */
865 heimbach 1.2
866     end
867    

  ViewVC Help
Powered by ViewVC 1.1.22