source: palm/trunk/SOURCE/data_output_spectra.f90 @ 1682

Last change on this file since 1682 was 1682, checked in by knoop, 9 years ago

Code annotations made doxygen readable

  • Property svn:keywords set to Id
File size: 21.8 KB
Line 
1!> @file data_output_spectra.f90
2!--------------------------------------------------------------------------------!
3! This file is part of PALM.
4!
5! PALM is free software: you can redistribute it and/or modify it under the terms
6! of the GNU General Public License as published by the Free Software Foundation,
7! either version 3 of the License, or (at your option) any later version.
8!
9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
10! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
11! A PARTICULAR PURPOSE.  See the GNU General Public License for more details.
12!
13! You should have received a copy of the GNU General Public License along with
14! PALM. If not, see <http://www.gnu.org/licenses/>.
15!
16! Copyright 1997-2014 Leibniz Universitaet Hannover
17!--------------------------------------------------------------------------------!
18!
19! Current revisions:
20! ------------------
21! Code annotations made doxygen readable
22!
23! Former revisions:
24! -----------------
25! $Id: data_output_spectra.f90 1682 2015-10-07 23:56:08Z knoop $
26!
27! 1353 2014-04-08 15:21:23Z heinze
28! REAL constants provided with KIND-attribute
29!
30! 1327 2014-03-21 11:00:16Z raasch
31! -netcdf output queries
32!
33! 1324 2014-03-21 09:13:16Z suehring
34! Bugfix: module statistics and module spectrum added, missing variables in ONLY
35! arguments added
36!
37! 1322 2014-03-20 16:38:49Z raasch
38! REAL functions provided with KIND-attribute
39!
40! 1320 2014-03-20 08:40:49Z raasch
41! ONLY-attribute added to USE-statements,
42! kind-parameters added to all INTEGER and REAL declaration statements,
43! kinds are defined in new module kinds,
44! revision history before 2012 removed,
45! comment fields (!:) to be used for variable explanations added to
46! all variable declaration statements
47!
48! 1318 2014-03-17 13:35:16Z raasch
49! module interfaces removed
50!
51! 1036 2012-10-22 13:43:42Z raasch
52! code put under GPL (PALM 3.9)
53!
54! 964 2012-07-26 09:14:24Z raasch
55! code for profil-output removed
56!
57! Revision 1.1  2001/01/05 15:14:20  raasch
58! Initial revision
59!
60!
61! Description:
62! ------------
63!> Writing spectra data on file, using a special format which allows
64!> plotting of these data with PROFIL-graphic-software
65!------------------------------------------------------------------------------!
66 SUBROUTINE data_output_spectra
67 
68#if defined( __spectra )
69
70    USE control_parameters,                                                    &
71        ONLY:  average_count_sp, averaging_interval_sp, dosp_time_count,       &
72               message_string, run_description_header,                         &
73               time_since_reference_point
74
75    USE cpulog,                                                                &
76        ONLY:  cpu_log, log_point
77
78    USE kinds
79
80    USE netcdf_control
81
82    USE pegrid
83
84    USE spectrum,                                                              &
85        ONLY:  data_output_sp, spectra_direction
86
87    USE statistics,                                                            &
88        ONLY:  spectrum_x, spectrum_y
89
90
91    IMPLICIT NONE
92
93    INTEGER(iwp) ::  cranz_x !<
94    INTEGER(iwp) ::  cranz_y !<
95    INTEGER(iwp) ::  m       !<
96    INTEGER(iwp) ::  pr      !<
97   
98    LOGICAL      ::  frame_x !<
99    LOGICAL      ::  frame_y !<
100
101    CALL cpu_log( log_point(31), 'data_output_spectra', 'start' )
102
103!
104!-- Output is only performed on PE0
105    IF ( myid == 0 )  THEN
106
107!
108!--    Open file for spectra output in NetCDF format
109       CALL check_open( 107 )
110
111!
112!--    Increment the counter for number of output times
113       dosp_time_count = dosp_time_count + 1
114
115#if defined( __netcdf )
116!
117!--    Update the spectra time axis
118       nc_stat = NF90_PUT_VAR( id_set_sp, id_var_time_sp,        &
119                               (/ time_since_reference_point /), &
120                               start = (/ dosp_time_count /), count = (/ 1 /) )
121       CALL handle_netcdf_error( 'data_output_spectra', 47 )
122#endif
123
124!
125!--    If necessary, calculate time average and reset average counter
126       IF ( average_count_sp == 0 )  THEN
127           message_string = 'no spectra data available'
128           CALL message( 'data_output_spectra', 'PA0186', 0, 0, 0, 6, 0 )
129       ENDIF
130       IF ( average_count_sp /= 1 )  THEN
131          spectrum_x = spectrum_x / REAL( average_count_sp, KIND=wp )
132          spectrum_y = spectrum_y / REAL( average_count_sp, KIND=wp )
133          average_count_sp = 0
134       ENDIF
135
136!
137!--    Loop over all spectra defined by the user
138       m = 1
139       DO WHILE ( data_output_sp(m) /= ' '  .AND.  m <= 10 )
140
141          SELECT CASE ( TRIM( data_output_sp(m) ) )
142
143             CASE ( 'u' )
144                pr = 1
145
146             CASE ( 'v' )
147                pr = 2
148
149             CASE ( 'w' )
150                pr = 3
151
152             CASE ( 'pt' )
153                pr = 4
154
155             CASE ( 'q' )
156                pr = 5
157
158             CASE DEFAULT
159!
160!--             The DEFAULT case is reached either if the parameter
161!--             data_output_sp(m) contains a wrong character string or if the
162!--             user has coded a special case in the user interface. There, the
163!--             subroutine user_spectra checks which of these two conditions
164!--             applies.
165                CALL user_spectra( 'data_output', m, pr )
166
167          END SELECT
168
169!
170!--       Output of spectra in NetCDF format
171!--       Output of x-spectra
172          IF ( INDEX( spectra_direction(m), 'x' ) /= 0 ) THEN
173             CALL output_spectra_netcdf( m, 'x' )
174          ENDIF
175!
176!--       Output of y-spectra
177          IF ( INDEX( spectra_direction(m), 'y' ) /= 0 ) THEN
178             CALL output_spectra_netcdf( m, 'y' )
179          ENDIF
180
181!
182!--       Increase counter for next spectrum
183          m = m + 1
184
185       ENDDO
186
187!
188!--    Reset spectra values
189       spectrum_x = 0.0_wp; spectrum_y = 0.0_wp
190
191    ENDIF
192
193    CALL cpu_log( log_point(31), 'data_output_spectra', 'stop' )
194
195#if defined( __parallel )
196!    CALL MPI_BARRIER( comm2d, ierr )  ! really necessary
197#endif
198
199#endif
200 END SUBROUTINE data_output_spectra
201
202
203!------------------------------------------------------------------------------!
204! Description:
205! ------------
206!> @todo Missing subroutine description.
207!------------------------------------------------------------------------------!
208 SUBROUTINE output_spectra_netcdf( nsp, direction )
209#if defined( __netcdf )
210
211    USE constants,                                                             &
212        ONLY:  pi
213
214    USE control_parameters,                                                    &
215        ONLY:  dosp_time_count
216
217    USE grid_variables,                                                        &
218        ONLY:  dx, dy
219
220    USE indices,                                                               &
221        ONLY:  nx, ny
222
223    USE kinds
224
225    USE netcdf_control
226
227    USE spectrum,                                                              &
228        ONLY:  n_sp_x, n_sp_y
229
230    USE statistics,                                                            &
231        ONLY:  spectrum_x, spectrum_y
232
233    IMPLICIT NONE
234
235    CHARACTER (LEN=1), INTENT(IN) ::  direction     !<
236
237    INTEGER(iwp), INTENT(IN)      ::  nsp           !<
238
239    INTEGER(iwp)                  ::  i             !<
240    INTEGER(iwp)                  ::  k             !<
241
242    REAL(wp)                      ::  frequency     !<
243
244    REAL(wp), DIMENSION(nx/2)     ::  netcdf_data_x !<
245    REAL(wp), DIMENSION(ny/2)     ::  netcdf_data_y !<
246
247
248    IF ( direction == 'x' )  THEN
249
250       DO  k = 1, n_sp_x
251
252          DO  i = 1, nx/2
253             frequency = 2.0_wp * pi * i / ( dx * ( nx + 1 ) )
254             netcdf_data_x(i) = frequency * spectrum_x(i,k,nsp)
255          ENDDO
256
257          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospx(nsp), netcdf_data_x, &
258                                  start = (/ 1, k, dosp_time_count /), &
259                                  count = (/ nx/2, 1, 1 /) )
260          CALL handle_netcdf_error( 'data_output_spectra', 348 )
261
262       ENDDO
263
264    ENDIF
265
266    IF ( direction == 'y' )  THEN
267
268       DO  k = 1, n_sp_y
269
270          DO  i = 1, ny/2
271             frequency = 2.0_wp * pi * i / ( dy * ( ny + 1 ) )
272             netcdf_data_y(i) = frequency * spectrum_y(i,k,nsp)
273          ENDDO
274
275          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospy(nsp), netcdf_data_y, &
276                                  start = (/ 1, k, dosp_time_count /), &
277                                  count = (/ ny/2, 1, 1 /) )
278          CALL handle_netcdf_error( 'data_output_spectra', 349 )
279
280       ENDDO
281
282    ENDIF
283
284#endif
285 END SUBROUTINE output_spectra_netcdf
286
287
288#if defined( __spectra )
289!------------------------------------------------------------------------------!
290! Description:
291! ------------
292!> @todo Missing subroutine description.
293!------------------------------------------------------------------------------!
294 SUBROUTINE data_output_spectra_x( m, cranz, pr, frame_written )
295
296    USE arrays_3d,                                                             &
297        ONLY:  zu, zw
298    USE constants,                                                             &
299        ONLY:  pi
300
301    USE control_parameters,                                                    &
302        ONLY:  averaging_interval_sp, run_description_header, simulated_time_chr
303
304    USE grid_variables,                                                        &
305        ONLY:  dx
306
307    USE indices,                                                               &
308        ONLY:  nx
309
310    USE kinds
311
312    USE pegrid
313
314    USE statistics,                                                            &
315        ONLY:  spectrum_x
316
317    USE spectrum,                                                              &
318        ONLY:  comp_spectra_level, header_char, lstyles, klist_x, n_sp_x,      &
319               plot_spectra_level, utext_char, ytext_char
320
321    IMPLICIT NONE
322
323    CHARACTER (LEN=30) ::  atext !<
324   
325    INTEGER(iwp)       ::  i     !<
326    INTEGER(iwp)       ::  j     !<
327    INTEGER(iwp)       ::  k     !<
328    INTEGER(iwp)       ::  m     !<
329    INTEGER(iwp)       ::  pr    !<
330   
331    LOGICAL            ::  frame_written   !<
332   
333    REAL(wp)           ::  frequency = 0.0_wp !<
334!
335!-- Variables needed for PROFIL-namelist
336    CHARACTER (LEN=80) ::  rtext                !<
337    CHARACTER (LEN=80) ::  utext                !<
338    CHARACTER (LEN=80) ::  xtext = 'k in m>->1' !<
339    CHARACTER (LEN=80) ::  ytext                !<
340
341    INTEGER(iwp)       ::  cranz       !<
342    INTEGER(iwp)       ::  labforx = 3 !<
343    INTEGER(iwp)       ::  labfory = 3 !<
344    INTEGER(iwp)       ::  legpos  = 3 !<
345    INTEGER(iwp)       ::  timodex = 1 !<
346   
347    INTEGER(iwp), DIMENSION(1:100) ::  cucol  = 1      !<
348    INTEGER(iwp), DIMENSION(1:100) ::  klist  = 999999 !<
349    INTEGER(iwp), DIMENSION(1:100) ::  lstyle = 0      !<
350   
351    LOGICAL ::  datleg = .TRUE. !<
352    LOGICAL ::  grid = .TRUE.   !<
353    LOGICAL ::  lclose = .TRUE. !<
354    LOGICAL ::  rand = .TRUE.   !<
355    LOGICAL ::  swap = .TRUE.   !<
356    LOGICAL ::  twoxa = .TRUE.  !<
357    LOGICAL ::  xlog = .TRUE.   !<
358    LOGICAL ::  ylog = .TRUE.   !<
359   
360    REAL(wp) ::  gwid = 0.1_wp    !<
361    REAL(wp) ::  rlegfak = 0.7_wp !<
362    REAL(wp) ::  uxmin            !<
363    REAL(wp) ::  uxmax            !<
364    REAL(wp) ::  uymin            !<
365    REAL(wp) ::  uymax            !<
366     
367    REAL(wp), DIMENSION(1:100) ::  lwid = 0.6_wp !<
368    REAL(wp), DIMENSION(100)   ::  uyma          !<
369    REAL(wp), DIMENSION(100)   ::  uymi          !<
370
371    NAMELIST /RAHMEN/  cranz, datleg, rtext, swap
372    NAMELIST /CROSS/   rand, cucol, grid, gwid, klist, labforx, labfory,      &
373                       legpos, lclose, lstyle, lwid, rlegfak, timodex, utext, &
374                       uxmin, uxmax, uymin, uymax, twoxa, xlog, xtext, ylog,  &
375                       ytext
376
377
378    rtext = '\0.5 ' // run_description_header
379
380!
381!-- Open parameter- and data-file
382    CALL check_open( 81 )
383    CALL check_open( 82 )
384
385!
386!-- Write file header,
387!-- write RAHMEN-parameters (pr=3: w-array is on zw, other arrys on zu,
388!-- pr serves as an index for output of strings (axis-labels) of the
389!-- different quantities u, v, w, pt and q)
390    DO  k = 1, n_sp_x
391       IF ( k < 100 )  THEN
392          IF ( pr == 3 )  THEN
393             WRITE ( 82, 100 )  '#', k, header_char( pr ),        &
394                                INT( zw(comp_spectra_level(k)) ), &
395                                simulated_time_chr
396          ELSE
397             WRITE ( 82, 100 )  '#', k, header_char( pr ),        &
398                                INT( zu(comp_spectra_level(k)) ), &
399                                simulated_time_chr
400          ENDIF
401       ELSE
402          IF ( pr == 3 )  THEN
403             WRITE ( 82, 101 )  '#', k, header_char( pr ),        &
404                                INT( zw(comp_spectra_level(k)) ), &
405                                simulated_time_chr
406          ELSE
407             WRITE ( 82, 101 )  '#', k, header_char( pr ),        &
408                                INT( zu(comp_spectra_level(k)) ), &
409                                simulated_time_chr
410          ENDIF
411       ENDIF
412    ENDDO
413
414    IF ( .NOT. frame_written )  THEN
415       WRITE ( 81, RAHMEN )
416       frame_written = .TRUE.
417    ENDIF
418
419!
420!-- Write all data and calculate uymi and uyma. They serve to calculate
421!-- the CROSS-parameters uymin and uymax
422    uymi = 999.999_wp; uyma = -999.999_wp
423    DO  i = 1, nx/2
424       frequency = 2.0_wp * pi * i / ( dx * ( nx + 1 ) )
425       WRITE ( 82, 102 )  frequency, ( frequency * spectrum_x(i,k,m), k = 1, &
426                          n_sp_x )
427       DO  k = 1, n_sp_x
428          uymi(k) = MIN( uymi(k), frequency * spectrum_x(i,k,m) )
429          uyma(k) = MAX( uyma(k), frequency * spectrum_x(i,k,m) )
430       ENDDO
431    ENDDO
432
433!
434!-- Determine CROSS-parameters
435    cucol(1:n_sp_x)  = (/ ( k, k = 1, n_sp_x ) /)
436    lstyle(1:n_sp_x) = (/ ( lstyles(k), k = 1, n_sp_x ) /)
437
438!
439!-- Calculate klist-values from the available comp_spectra_level values
440    i = 1; k = 1
441    DO WHILE ( i <= 100  .AND.  plot_spectra_level(i) /= 999999 )
442       DO WHILE ( k <= n_sp_x  .AND. &
443                  plot_spectra_level(i) >= comp_spectra_level(k) )
444          IF ( plot_spectra_level(i) == comp_spectra_level(k) )  THEN
445             klist(i) = k + klist_x
446          ELSE
447             uymi(k) =  999.999_wp
448             uyma(k) = -999.999_wp
449          ENDIF
450          k = k + 1
451       ENDDO
452       i = i + 1
453    ENDDO
454    uymi(k:n_sp_x) =  999.999_wp
455    uyma(k:n_sp_x) = -999.999_wp
456    utext = 'x'//utext_char( pr )
457    IF ( averaging_interval_sp /= 0.0_wp ) THEN
458       WRITE ( atext, 104 )  averaging_interval_sp
459       utext = TRIM(utext) // ',  ' // TRIM( atext )
460    ENDIF
461    uxmin = 0.8_wp * 2.0_wp * pi        / ( dx * ( nx + 1 ) )
462    uxmax = 1.2_wp * 2.0_wp * pi * nx/2 / ( dx * ( nx + 1 ) )
463    uymin = 0.8_wp * MIN (  999.999_wp, MINVAL ( uymi ) )
464    uymax = 1.2_wp * MAX ( -999.999_wp, MAXVAL ( uyma ) )
465    ytext = ytext_char( pr )
466
467!
468!-- Output of CROSS-parameters
469    WRITE ( 81, CROSS )
470
471!
472!-- Increase counter by the number of profiles written in the actual block
473    klist_x = klist_x + n_sp_x
474
475!
476!-- Write end-mark
477    WRITE ( 82, 103 )
478
479!
480!-- Close parameter- and data-file
481    CALL close_file( 81 )
482    CALL close_file( 82 )
483
484!
485!-- Formats
486100 FORMAT (A,I1,1X,A,1X,I4,'m ',A)
487101 FORMAT (A,I2,1X,A,1X,I4,'m ',A)
488102 FORMAT (E15.7,100(1X,E15.7))
489103 FORMAT ('NEXT')
490104 FORMAT ('time averaged over',F7.1,' s')
491
492 END SUBROUTINE data_output_spectra_x
493
494
495!------------------------------------------------------------------------------!
496! Description:
497! ------------
498!> @todo Missing subroutine description.
499!------------------------------------------------------------------------------!
500 SUBROUTINE data_output_spectra_y( m, cranz, pr, frame_written )
501
502    USE arrays_3d,                                                             &
503        ONLY:  zu, zw
504 
505    USE constants,                                                             &
506        ONLY:  pi
507
508    USE control_parameters,                                                    &
509        ONLY:  averaging_interval_sp, run_description_header, simulated_time_chr
510
511    USE grid_variables,                                                        &
512        ONLY:  dy
513
514    USE indices,                                                               &
515        ONLY:  ny
516
517    USE kinds
518
519    USE pegrid
520   
521    USE statistics,                                                             &
522        ONLY:  spectrum_y
523
524    USE spectrum,                                                              &
525        ONLY:  comp_spectra_level, header_char, klist_y, lstyles, n_sp_y,      &
526               plot_spectra_level, utext_char, ytext_char
527
528    IMPLICIT NONE
529
530   
531    CHARACTER (LEN=30) ::  atext !<
532   
533    INTEGER(iwp)       ::  i     !<
534    INTEGER(iwp)       ::  j     !<
535    INTEGER(iwp)       ::  k     !<
536    INTEGER(iwp)       ::  m     !<
537    INTEGER(iwp)       ::  pr    !<
538   
539    LOGICAL            :: frame_written   !<
540   
541    REAL(wp)           :: frequency = 0.0_wp !<
542
543!
544!-- Variables needed for PROFIL-namelist
545    CHARACTER (LEN=80) ::  rtext                !<
546    CHARACTER (LEN=80) ::  utext                !<
547    CHARACTER (LEN=80) ::  xtext = 'k in m>->1' !<
548    CHARACTER (LEN=80) ::  ytext                !<
549
550    INTEGER(iwp) ::  cranz       !<
551    INTEGER(iwp) ::  labforx = 3 !<
552    INTEGER(iwp) ::  labfory = 3 !<
553    INTEGER(iwp) ::  legpos  = 3 !<
554    INTEGER(iwp) ::  timodex = 1 !<
555   
556    INTEGER(iwp), DIMENSION(1:100) ::  cucol  = 1      !<
557    INTEGER(iwp), DIMENSION(1:100) ::  klist  = 999999 !<
558    INTEGER(iwp), DIMENSION(1:100) ::  lstyle = 0      !<
559   
560    LOGICAL ::  datleg = .TRUE. !<
561    LOGICAL ::  grid = .TRUE.   !<
562    LOGICAL ::  lclose = .TRUE. !<
563    LOGICAL ::  rand = .TRUE.   !<
564    LOGICAL ::  swap = .TRUE.   !<
565    LOGICAL ::  twoxa = .TRUE.  !<
566    LOGICAL ::  xlog = .TRUE.   !<
567    LOGICAL ::  ylog = .TRUE.   !<
568   
569    REAL(wp) ::  gwid = 0.1_wp     !<
570    REAL(wp) ::  rlegfak = 0.7_wp  !<
571    REAL(wp) ::  uxmin             !<
572    REAL(wp) ::  uxmax             !<
573    REAL(wp) ::  uymin             !<
574    REAL(wp) ::  uymax             !<
575   
576    REAL(wp), DIMENSION(1:100) ::  lwid = 0.6_wp !<
577   
578    REAL(wp), DIMENSION(100)   ::  uyma          !<
579    REAL(wp), DIMENSION(100)   ::  uymi          !<
580
581    NAMELIST /RAHMEN/  cranz, datleg, rtext, swap
582    NAMELIST /CROSS/   rand, cucol, grid, gwid, klist, labforx, labfory,      &
583                       legpos, lclose, lstyle, lwid, rlegfak, timodex, utext, &
584                       uxmin, uxmax, uymin, uymax, twoxa, xlog, xtext, ylog,  &
585                       ytext
586
587
588    rtext = '\0.5 ' // run_description_header
589
590!
591!-- Open parameter- and data-file
592    CALL check_open( 83 )
593    CALL check_open( 84 )
594
595!
596!-- Write file header,
597!-- write RAHMEN-parameters (pr=3: w-array is on zw, other arrys on zu,
598!-- pr serves as an index for output of strings (axis-labels) of the
599!-- different quantities u, v, w, pt and q)
600    DO  k = 1, n_sp_y
601       IF ( k < 100 )  THEN
602          IF ( pr == 3 ) THEN
603             WRITE ( 84, 100 )  '#', k, header_char( pr ),        &
604                                INT( zw(comp_spectra_level(k)) ), &
605                                simulated_time_chr
606          ELSE
607             WRITE ( 84, 100 )  '#', k, header_char( pr ),        &
608                                INT( zu(comp_spectra_level(k)) ), &
609                                simulated_time_chr
610          ENDIF
611       ELSE
612          IF ( pr == 3 )  THEN
613             WRITE ( 84, 101 )  '#', k, header_char( pr ),        &
614                                INT( zw(comp_spectra_level(k)) ), &
615                                simulated_time_chr
616          ELSE
617             WRITE ( 84, 101 )  '#', k, header_char( pr ),        &
618                                INT( zu(comp_spectra_level(k)) ), &
619                                simulated_time_chr
620          ENDIF
621       ENDIF
622    ENDDO
623
624    IF ( .NOT. frame_written )  THEN
625       WRITE ( 83, RAHMEN )
626       frame_written = .TRUE.
627    ENDIF
628
629!
630!-- Write all data and calculate uymi and uyma. They serve to calculate
631!-- the CROSS-parameters uymin and uymax
632    uymi = 999.999_wp; uyma = -999.999_wp
633    DO  j = 1, ny/2
634       frequency = 2.0_wp * pi * j / ( dy * ( ny + 1 ) )
635       WRITE ( 84, 102 ) frequency, ( frequency * spectrum_y(j,k,m), &
636                                      k = 1, n_sp_y ) 
637       DO k = 1, n_sp_y
638          uymi(k) = MIN( uymi(k), frequency * spectrum_y(j,k,m) )
639          uyma(k) = MAX( uyma(k), frequency * spectrum_y(j,k,m) )
640       ENDDO
641    ENDDO
642
643!
644!-- Determine CROSS-parameters
645    cucol(1:n_sp_y)  = (/ ( k, k = 1, n_sp_y ) /)
646    lstyle(1:n_sp_y) = (/ ( lstyles(k), k = 1, n_sp_y ) /)
647
648!
649!-- Calculate klist-values from the available comp_spectra_level values
650    j = 1; k = 1
651    DO WHILE ( j <= 100  .AND.  plot_spectra_level(j) /= 999999 )
652       DO WHILE ( k <= n_sp_y  .AND. &
653                  plot_spectra_level(j) >= comp_spectra_level(k) )
654          IF ( plot_spectra_level(j) == comp_spectra_level(k) )  THEN
655             klist(j) = k + klist_y
656          ELSE
657             uymi(k) =  999.999_wp
658             uyma(k) = -999.999_wp
659          ENDIF
660          k = k + 1
661       ENDDO
662       j = j + 1
663    ENDDO
664    uymi(k:n_sp_y) =  999.999_wp
665    uyma(k:n_sp_y) = -999.999_wp
666    utext = 'y'//utext_char( pr )
667    IF ( averaging_interval_sp /= 0.0_wp )  THEN
668       WRITE ( atext, 104 )  averaging_interval_sp
669       utext = TRIM(utext) // ',  ' // TRIM( atext )
670    ENDIF
671    uxmin = 0.8_wp * 2.0_wp * pi        / ( dy * ( ny + 1 ) )
672    uxmax = 1.2_wp * 2.0_wp * pi * ny/2 / ( dy * ( ny + 1 ) )
673    uymin = 0.8_wp * MIN (  999.999_wp, MINVAL ( uymi ) )
674    uymax = 1.2_wp * MAX ( -999.999_wp, MAXVAL ( uyma ) )
675    ytext = ytext_char( pr )
676
677!
678!-- Output CROSS-parameters
679    WRITE ( 83, CROSS )
680
681!
682!-- Increase counter by the number of profiles written in the actual block
683    klist_y = klist_y + n_sp_y
684
685!
686!-- Write end-mark
687    WRITE ( 84, 103 ) 
688
689!
690!-- Close parameter- and data-file
691    CALL close_file( 83 )
692    CALL close_file( 84 )
693
694!
695!-- Formats
696100 FORMAT (A,I1,1X,A,1X,I4,'m ',A)
697101 FORMAT (A,I2,1X,A,1X,I4,'m ',A)
698102 FORMAT (E15.7,100(1X,E15.7))
699103 FORMAT ('NEXT')
700104 FORMAT ('time averaged over',F7.1,' s')
701
702 END SUBROUTINE data_output_spectra_y
703#endif
Note: See TracBrowser for help on using the repository browser.