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

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

last commit documented

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