SUBROUTINE data_output_spectra !--------------------------------------------------------------------------------! ! This file is part of PALM. ! ! PALM is free software: you can redistribute it and/or modify it under the terms ! of the GNU General Public License as published by the Free Software Foundation, ! either version 3 of the License, or (at your option) any later version. ! ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR ! A PARTICULAR PURPOSE. See the GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License along with ! PALM. If not, see . ! ! Copyright 1997-2014 Leibniz Universitaet Hannover !--------------------------------------------------------------------------------! ! ! Current revisions: ! ------------------ ! ! ! Former revisions: ! ----------------- ! $Id: data_output_spectra.f90 1354 2014-04-08 15:22:57Z hoffmann $ ! ! 1353 2014-04-08 15:21:23Z heinze ! REAL constants provided with KIND-attribute ! ! 1327 2014-03-21 11:00:16Z raasch ! -netcdf output queries ! ! 1324 2014-03-21 09:13:16Z suehring ! Bugfix: module statistics and module spectrum added, missing variables in ONLY ! arguments added ! ! 1322 2014-03-20 16:38:49Z raasch ! REAL functions provided with KIND-attribute ! ! 1320 2014-03-20 08:40:49Z raasch ! ONLY-attribute added to USE-statements, ! kind-parameters added to all INTEGER and REAL declaration statements, ! kinds are defined in new module kinds, ! revision history before 2012 removed, ! comment fields (!:) to be used for variable explanations added to ! all variable declaration statements ! ! 1318 2014-03-17 13:35:16Z raasch ! module interfaces removed ! ! 1036 2012-10-22 13:43:42Z raasch ! code put under GPL (PALM 3.9) ! ! 964 2012-07-26 09:14:24Z raasch ! code for profil-output removed ! ! Revision 1.1 2001/01/05 15:14:20 raasch ! Initial revision ! ! ! Description: ! ------------ ! Writing spectra data on file, using a special format which allows ! plotting of these data with PROFIL-graphic-software !------------------------------------------------------------------------------! #if defined( __spectra ) USE control_parameters, & ONLY: average_count_sp, averaging_interval_sp, dosp_time_count, & message_string, run_description_header, & time_since_reference_point USE cpulog, & ONLY: cpu_log, log_point USE kinds USE netcdf_control USE pegrid USE spectrum, & ONLY: data_output_sp, spectra_direction USE statistics, & ONLY: spectrum_x, spectrum_y IMPLICIT NONE INTEGER(iwp) :: cranz_x !: INTEGER(iwp) :: cranz_y !: INTEGER(iwp) :: m !: INTEGER(iwp) :: pr !: LOGICAL :: frame_x !: LOGICAL :: frame_y !: CALL cpu_log( log_point(31), 'data_output_spectra', 'start' ) ! !-- Output is only performed on PE0 IF ( myid == 0 ) THEN ! !-- Open file for spectra output in NetCDF format CALL check_open( 107 ) ! !-- Increment the counter for number of output times dosp_time_count = dosp_time_count + 1 #if defined( __netcdf ) ! !-- Update the spectra time axis nc_stat = NF90_PUT_VAR( id_set_sp, id_var_time_sp, & (/ time_since_reference_point /), & start = (/ dosp_time_count /), count = (/ 1 /) ) CALL handle_netcdf_error( 'data_output_spectra', 47 ) #endif ! !-- If necessary, calculate time average and reset average counter IF ( average_count_sp == 0 ) THEN message_string = 'no spectra data available' CALL message( 'data_output_spectra', 'PA0186', 0, 0, 0, 6, 0 ) ENDIF IF ( average_count_sp /= 1 ) THEN spectrum_x = spectrum_x / REAL( average_count_sp, KIND=wp ) spectrum_y = spectrum_y / REAL( average_count_sp, KIND=wp ) average_count_sp = 0 ENDIF ! !-- Loop over all spectra defined by the user m = 1 DO WHILE ( data_output_sp(m) /= ' ' .AND. m <= 10 ) SELECT CASE ( TRIM( data_output_sp(m) ) ) CASE ( 'u' ) pr = 1 CASE ( 'v' ) pr = 2 CASE ( 'w' ) pr = 3 CASE ( 'pt' ) pr = 4 CASE ( 'q' ) pr = 5 CASE DEFAULT ! !-- The DEFAULT case is reached either if the parameter !-- data_output_sp(m) contains a wrong character string or if the !-- user has coded a special case in the user interface. There, the !-- subroutine user_spectra checks which of these two conditions !-- applies. CALL user_spectra( 'data_output', m, pr ) END SELECT ! !-- Output of spectra in NetCDF format !-- Output of x-spectra IF ( INDEX( spectra_direction(m), 'x' ) /= 0 ) THEN CALL output_spectra_netcdf( m, 'x' ) ENDIF ! !-- Output of y-spectra IF ( INDEX( spectra_direction(m), 'y' ) /= 0 ) THEN CALL output_spectra_netcdf( m, 'y' ) ENDIF ! !-- Increase counter for next spectrum m = m + 1 ENDDO ! !-- Reset spectra values spectrum_x = 0.0_wp; spectrum_y = 0.0_wp ENDIF CALL cpu_log( log_point(31), 'data_output_spectra', 'stop' ) #if defined( __parallel ) ! CALL MPI_BARRIER( comm2d, ierr ) ! really necessary #endif #endif END SUBROUTINE data_output_spectra SUBROUTINE output_spectra_netcdf( nsp, direction ) #if defined( __netcdf ) USE constants, & ONLY: pi USE control_parameters, & ONLY: dosp_time_count USE grid_variables, & ONLY: dx, dy USE indices, & ONLY: nx, ny USE kinds USE netcdf_control USE spectrum, & ONLY: n_sp_x, n_sp_y USE statistics, & ONLY: spectrum_x, spectrum_y IMPLICIT NONE CHARACTER (LEN=1), INTENT(IN) :: direction !: INTEGER(iwp), INTENT(IN) :: nsp !: INTEGER(iwp) :: i !: INTEGER(iwp) :: k !: REAL(wp) :: frequency !: REAL(wp), DIMENSION(nx/2) :: netcdf_data_x !: REAL(wp), DIMENSION(ny/2) :: netcdf_data_y !: IF ( direction == 'x' ) THEN DO k = 1, n_sp_x DO i = 1, nx/2 frequency = 2.0_wp * pi * i / ( dx * ( nx + 1 ) ) netcdf_data_x(i) = frequency * spectrum_x(i,k,nsp) ENDDO nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospx(nsp), netcdf_data_x, & start = (/ 1, k, dosp_time_count /), & count = (/ nx/2, 1, 1 /) ) CALL handle_netcdf_error( 'data_output_spectra', 348 ) ENDDO ENDIF IF ( direction == 'y' ) THEN DO k = 1, n_sp_y DO i = 1, ny/2 frequency = 2.0_wp * pi * i / ( dy * ( ny + 1 ) ) netcdf_data_y(i) = frequency * spectrum_y(i,k,nsp) ENDDO nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospy(nsp), netcdf_data_y, & start = (/ 1, k, dosp_time_count /), & count = (/ ny/2, 1, 1 /) ) CALL handle_netcdf_error( 'data_output_spectra', 349 ) ENDDO ENDIF #endif END SUBROUTINE output_spectra_netcdf #if defined( __spectra ) SUBROUTINE data_output_spectra_x( m, cranz, pr, frame_written ) USE arrays_3d, & ONLY: zu, zw USE constants, & ONLY: pi USE control_parameters, & ONLY: averaging_interval_sp, run_description_header, simulated_time_chr USE grid_variables, & ONLY: dx USE indices, & ONLY: nx USE kinds USE pegrid USE statistics, & ONLY: spectrum_x USE spectrum, & ONLY: comp_spectra_level, header_char, lstyles, klist_x, n_sp_x, & plot_spectra_level, utext_char, ytext_char IMPLICIT NONE CHARACTER (LEN=30) :: atext !: INTEGER(iwp) :: i !: INTEGER(iwp) :: j !: INTEGER(iwp) :: k !: INTEGER(iwp) :: m !: INTEGER(iwp) :: pr !: LOGICAL :: frame_written !: REAL(wp) :: frequency = 0.0_wp !: ! !-- Variables needed for PROFIL-namelist CHARACTER (LEN=80) :: rtext !: CHARACTER (LEN=80) :: utext !: CHARACTER (LEN=80) :: xtext = 'k in m>->1' !: CHARACTER (LEN=80) :: ytext !: INTEGER(iwp) :: cranz !: INTEGER(iwp) :: labforx = 3 !: INTEGER(iwp) :: labfory = 3 !: INTEGER(iwp) :: legpos = 3 !: INTEGER(iwp) :: timodex = 1 !: INTEGER(iwp), DIMENSION(1:100) :: cucol = 1 !: INTEGER(iwp), DIMENSION(1:100) :: klist = 999999 !: INTEGER(iwp), DIMENSION(1:100) :: lstyle = 0 !: LOGICAL :: datleg = .TRUE. !: LOGICAL :: grid = .TRUE. !: LOGICAL :: lclose = .TRUE. !: LOGICAL :: rand = .TRUE. !: LOGICAL :: swap = .TRUE. !: LOGICAL :: twoxa = .TRUE. !: LOGICAL :: xlog = .TRUE. !: LOGICAL :: ylog = .TRUE. !: REAL(wp) :: gwid = 0.1_wp !: REAL(wp) :: rlegfak = 0.7_wp !: REAL(wp) :: uxmin !: REAL(wp) :: uxmax !: REAL(wp) :: uymin !: REAL(wp) :: uymax !: REAL(wp), DIMENSION(1:100) :: lwid = 0.6_wp !: REAL(wp), DIMENSION(100) :: uyma !: REAL(wp), DIMENSION(100) :: uymi !: NAMELIST /RAHMEN/ cranz, datleg, rtext, swap NAMELIST /CROSS/ rand, cucol, grid, gwid, klist, labforx, labfory, & legpos, lclose, lstyle, lwid, rlegfak, timodex, utext, & uxmin, uxmax, uymin, uymax, twoxa, xlog, xtext, ylog, & ytext rtext = '\0.5 ' // run_description_header ! !-- Open parameter- and data-file CALL check_open( 81 ) CALL check_open( 82 ) ! !-- Write file header, !-- write RAHMEN-parameters (pr=3: w-array is on zw, other arrys on zu, !-- pr serves as an index for output of strings (axis-labels) of the !-- different quantities u, v, w, pt and q) DO k = 1, n_sp_x IF ( k < 100 ) THEN IF ( pr == 3 ) THEN WRITE ( 82, 100 ) '#', k, header_char( pr ), & INT( zw(comp_spectra_level(k)) ), & simulated_time_chr ELSE WRITE ( 82, 100 ) '#', k, header_char( pr ), & INT( zu(comp_spectra_level(k)) ), & simulated_time_chr ENDIF ELSE IF ( pr == 3 ) THEN WRITE ( 82, 101 ) '#', k, header_char( pr ), & INT( zw(comp_spectra_level(k)) ), & simulated_time_chr ELSE WRITE ( 82, 101 ) '#', k, header_char( pr ), & INT( zu(comp_spectra_level(k)) ), & simulated_time_chr ENDIF ENDIF ENDDO IF ( .NOT. frame_written ) THEN WRITE ( 81, RAHMEN ) frame_written = .TRUE. ENDIF ! !-- Write all data and calculate uymi and uyma. They serve to calculate !-- the CROSS-parameters uymin and uymax uymi = 999.999_wp; uyma = -999.999_wp DO i = 1, nx/2 frequency = 2.0_wp * pi * i / ( dx * ( nx + 1 ) ) WRITE ( 82, 102 ) frequency, ( frequency * spectrum_x(i,k,m), k = 1, & n_sp_x ) DO k = 1, n_sp_x uymi(k) = MIN( uymi(k), frequency * spectrum_x(i,k,m) ) uyma(k) = MAX( uyma(k), frequency * spectrum_x(i,k,m) ) ENDDO ENDDO ! !-- Determine CROSS-parameters cucol(1:n_sp_x) = (/ ( k, k = 1, n_sp_x ) /) lstyle(1:n_sp_x) = (/ ( lstyles(k), k = 1, n_sp_x ) /) ! !-- Calculate klist-values from the available comp_spectra_level values i = 1; k = 1 DO WHILE ( i <= 100 .AND. plot_spectra_level(i) /= 999999 ) DO WHILE ( k <= n_sp_x .AND. & plot_spectra_level(i) >= comp_spectra_level(k) ) IF ( plot_spectra_level(i) == comp_spectra_level(k) ) THEN klist(i) = k + klist_x ELSE uymi(k) = 999.999_wp uyma(k) = -999.999_wp ENDIF k = k + 1 ENDDO i = i + 1 ENDDO uymi(k:n_sp_x) = 999.999_wp uyma(k:n_sp_x) = -999.999_wp utext = 'x'//utext_char( pr ) IF ( averaging_interval_sp /= 0.0_wp ) THEN WRITE ( atext, 104 ) averaging_interval_sp utext = TRIM(utext) // ', ' // TRIM( atext ) ENDIF uxmin = 0.8_wp * 2.0_wp * pi / ( dx * ( nx + 1 ) ) uxmax = 1.2_wp * 2.0_wp * pi * nx/2 / ( dx * ( nx + 1 ) ) uymin = 0.8_wp * MIN ( 999.999_wp, MINVAL ( uymi ) ) uymax = 1.2_wp * MAX ( -999.999_wp, MAXVAL ( uyma ) ) ytext = ytext_char( pr ) ! !-- Output of CROSS-parameters WRITE ( 81, CROSS ) ! !-- Increase counter by the number of profiles written in the actual block klist_x = klist_x + n_sp_x ! !-- Write end-mark WRITE ( 82, 103 ) ! !-- Close parameter- and data-file CALL close_file( 81 ) CALL close_file( 82 ) ! !-- Formats 100 FORMAT (A,I1,1X,A,1X,I4,'m ',A) 101 FORMAT (A,I2,1X,A,1X,I4,'m ',A) 102 FORMAT (E15.7,100(1X,E15.7)) 103 FORMAT ('NEXT') 104 FORMAT ('time averaged over',F7.1,' s') END SUBROUTINE data_output_spectra_x SUBROUTINE data_output_spectra_y( m, cranz, pr, frame_written ) USE arrays_3d, & ONLY: zu, zw USE constants, & ONLY: pi USE control_parameters, & ONLY: averaging_interval_sp, run_description_header, simulated_time_chr USE grid_variables, & ONLY: dy USE indices, & ONLY: ny USE kinds USE pegrid USE statistics, & ONLY: spectrum_y USE spectrum, & ONLY: comp_spectra_level, header_char, klist_y, lstyles, n_sp_y, & plot_spectra_level, utext_char, ytext_char IMPLICIT NONE CHARACTER (LEN=30) :: atext !: INTEGER(iwp) :: i !: INTEGER(iwp) :: j !: INTEGER(iwp) :: k !: INTEGER(iwp) :: m !: INTEGER(iwp) :: pr !: LOGICAL :: frame_written !: REAL(wp) :: frequency = 0.0_wp !: ! !-- Variables needed for PROFIL-namelist CHARACTER (LEN=80) :: rtext !: CHARACTER (LEN=80) :: utext !: CHARACTER (LEN=80) :: xtext = 'k in m>->1' !: CHARACTER (LEN=80) :: ytext !: INTEGER(iwp) :: cranz !: INTEGER(iwp) :: labforx = 3 !: INTEGER(iwp) :: labfory = 3 !: INTEGER(iwp) :: legpos = 3 !: INTEGER(iwp) :: timodex = 1 !: INTEGER(iwp), DIMENSION(1:100) :: cucol = 1 !: INTEGER(iwp), DIMENSION(1:100) :: klist = 999999 !: INTEGER(iwp), DIMENSION(1:100) :: lstyle = 0 !: LOGICAL :: datleg = .TRUE. !: LOGICAL :: grid = .TRUE. !: LOGICAL :: lclose = .TRUE. !: LOGICAL :: rand = .TRUE. !: LOGICAL :: swap = .TRUE. !: LOGICAL :: twoxa = .TRUE. !: LOGICAL :: xlog = .TRUE. !: LOGICAL :: ylog = .TRUE. !: REAL(wp) :: gwid = 0.1_wp !: REAL(wp) :: rlegfak = 0.7_wp !: REAL(wp) :: uxmin !: REAL(wp) :: uxmax !: REAL(wp) :: uymin !: REAL(wp) :: uymax !: REAL(wp), DIMENSION(1:100) :: lwid = 0.6_wp !: REAL(wp), DIMENSION(100) :: uyma !: REAL(wp), DIMENSION(100) :: uymi !: NAMELIST /RAHMEN/ cranz, datleg, rtext, swap NAMELIST /CROSS/ rand, cucol, grid, gwid, klist, labforx, labfory, & legpos, lclose, lstyle, lwid, rlegfak, timodex, utext, & uxmin, uxmax, uymin, uymax, twoxa, xlog, xtext, ylog, & ytext rtext = '\0.5 ' // run_description_header ! !-- Open parameter- and data-file CALL check_open( 83 ) CALL check_open( 84 ) ! !-- Write file header, !-- write RAHMEN-parameters (pr=3: w-array is on zw, other arrys on zu, !-- pr serves as an index for output of strings (axis-labels) of the !-- different quantities u, v, w, pt and q) DO k = 1, n_sp_y IF ( k < 100 ) THEN IF ( pr == 3 ) THEN WRITE ( 84, 100 ) '#', k, header_char( pr ), & INT( zw(comp_spectra_level(k)) ), & simulated_time_chr ELSE WRITE ( 84, 100 ) '#', k, header_char( pr ), & INT( zu(comp_spectra_level(k)) ), & simulated_time_chr ENDIF ELSE IF ( pr == 3 ) THEN WRITE ( 84, 101 ) '#', k, header_char( pr ), & INT( zw(comp_spectra_level(k)) ), & simulated_time_chr ELSE WRITE ( 84, 101 ) '#', k, header_char( pr ), & INT( zu(comp_spectra_level(k)) ), & simulated_time_chr ENDIF ENDIF ENDDO IF ( .NOT. frame_written ) THEN WRITE ( 83, RAHMEN ) frame_written = .TRUE. ENDIF ! !-- Write all data and calculate uymi and uyma. They serve to calculate !-- the CROSS-parameters uymin and uymax uymi = 999.999_wp; uyma = -999.999_wp DO j = 1, ny/2 frequency = 2.0_wp * pi * j / ( dy * ( ny + 1 ) ) WRITE ( 84, 102 ) frequency, ( frequency * spectrum_y(j,k,m), & k = 1, n_sp_y ) DO k = 1, n_sp_y uymi(k) = MIN( uymi(k), frequency * spectrum_y(j,k,m) ) uyma(k) = MAX( uyma(k), frequency * spectrum_y(j,k,m) ) ENDDO ENDDO ! !-- Determine CROSS-parameters cucol(1:n_sp_y) = (/ ( k, k = 1, n_sp_y ) /) lstyle(1:n_sp_y) = (/ ( lstyles(k), k = 1, n_sp_y ) /) ! !-- Calculate klist-values from the available comp_spectra_level values j = 1; k = 1 DO WHILE ( j <= 100 .AND. plot_spectra_level(j) /= 999999 ) DO WHILE ( k <= n_sp_y .AND. & plot_spectra_level(j) >= comp_spectra_level(k) ) IF ( plot_spectra_level(j) == comp_spectra_level(k) ) THEN klist(j) = k + klist_y ELSE uymi(k) = 999.999_wp uyma(k) = -999.999_wp ENDIF k = k + 1 ENDDO j = j + 1 ENDDO uymi(k:n_sp_y) = 999.999_wp uyma(k:n_sp_y) = -999.999_wp utext = 'y'//utext_char( pr ) IF ( averaging_interval_sp /= 0.0_wp ) THEN WRITE ( atext, 104 ) averaging_interval_sp utext = TRIM(utext) // ', ' // TRIM( atext ) ENDIF uxmin = 0.8_wp * 2.0_wp * pi / ( dy * ( ny + 1 ) ) uxmax = 1.2_wp * 2.0_wp * pi * ny/2 / ( dy * ( ny + 1 ) ) uymin = 0.8_wp * MIN ( 999.999_wp, MINVAL ( uymi ) ) uymax = 1.2_wp * MAX ( -999.999_wp, MAXVAL ( uyma ) ) ytext = ytext_char( pr ) ! !-- Output CROSS-parameters WRITE ( 83, CROSS ) ! !-- Increase counter by the number of profiles written in the actual block klist_y = klist_y + n_sp_y ! !-- Write end-mark WRITE ( 84, 103 ) ! !-- Close parameter- and data-file CALL close_file( 83 ) CALL close_file( 84 ) ! !-- Formats 100 FORMAT (A,I1,1X,A,1X,I4,'m ',A) 101 FORMAT (A,I2,1X,A,1X,I4,'m ',A) 102 FORMAT (E15.7,100(1X,E15.7)) 103 FORMAT ('NEXT') 104 FORMAT ('time averaged over',F7.1,' s') END SUBROUTINE data_output_spectra_y #endif