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

Last change on this file since 1320 was 1320, checked in by raasch, 10 years ago

ONLY-attribute added to USE-statements,
kind-parameters added to all INTEGER and REAL declaration statements,
kinds are defined in new module kinds,
old module precision_kind is removed,
revision history before 2012 removed,
comment fields (!:) to be used for variable explanations added to all variable declaration statements

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