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

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

REAL functions and a lot of REAL constants provided with KIND-attribute,
some small bugfixes

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