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

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

Changed:


-s real64 removed (.mrun.config.hlrnIII)
-r8 removed (.mrun.config.imuk)
deleted: .mrun.config.imuk_ice2_netcdf4 .mrun.config.imuk_hlrn

REAL constants defined as wp-kind in modules

"baroclinicity" renamed "baroclinity", "ocean version" replaced by
"ocean mode"

code parts concerning old output formats "iso2d" and "avs" removed.
netCDF is the only remaining output format.

Errors:


bugfix: duplicate error message 56 removed

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