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

Last change on this file since 4828 was 4828, checked in by Giersch, 3 years ago

Copyright updated to year 2021, interface pmc_sort removed to accelarate the nesting code

  • Property svn:keywords set to Id
File size: 8.3 KB
RevLine 
[1682]1!> @file data_output_spectra.f90
[4577]2!--------------------------------------------------------------------------------------------------!
[2696]3! This file is part of the PALM model system.
[1036]4!
[4577]5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
6! Public License as published by the Free Software Foundation, either version 3 of the License, or
7! (at your option) any later version.
[1036]8!
[4577]9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
11! Public License for more details.
[1036]12!
[4577]13! You should have received a copy of the GNU General Public License along with PALM. If not, see
14! <http://www.gnu.org/licenses/>.
[1036]15!
[4828]16! Copyright 1997-2021 Leibniz Universitaet Hannover
[4577]17!--------------------------------------------------------------------------------------------------!
[1036]18!
[254]19! Current revisions:
[1327]20! ------------------
[1834]21!
[2001]22!
[1321]23! Former revisions:
24! -----------------
25! $Id: data_output_spectra.f90 4828 2021-01-05 11:21:41Z Giersch $
[4577]26! file re-formatted to follow the PALM coding standard
27!
28! 4360 2020-01-07 11:25:50Z suehring
[4182]29! Corrected "Former revisions" section
[4577]30!
[4182]31! 3655 2019-01-07 16:51:22Z knoop
[3547]32! variables documented
[1321]33!
[4182]34! Revision 1.1  2001/01/05 15:14:20  raasch
35! Initial revision
36!
37!
[1]38! Description:
39! ------------
[1682]40!> Writing spectra data on file, using a special format which allows
41!> plotting of these data with PROFIL-graphic-software
[4577]42!--------------------------------------------------------------------------------------------------!
[1682]43 SUBROUTINE data_output_spectra
[4577]44
[1783]45#if defined( __netcdf )
[4577]46    USE control_parameters,                                                                        &
[3241]47        ONLY:  message_string, time_since_reference_point
[1320]48
[4577]49    USE cpulog,                                                                                    &
[1320]50        ONLY:  cpu_log, log_point
51
52    USE kinds
53
[1783]54    USE NETCDF
[1320]55
[4577]56    USE netcdf_interface,                                                                          &
[1783]57        ONLY:  id_set_sp, id_var_time_sp, nc_stat, netcdf_handle_error
58
[1]59    USE pegrid
60
[4577]61    USE spectra_mod,                                                                               &
62        ONLY:  average_count_sp, averaging_interval_sp, comp_spectra_level, data_output_sp,        &
63               dosp_time_count, spectra_direction, spectrum_x, spectrum_y
[1]64
[1320]65
[1]66    IMPLICIT NONE
67
[3547]68    INTEGER(iwp) ::  m       !< running index over spectra output
69    INTEGER(iwp) ::  pr      !< index used to assign default quantities to data output
[4577]70
[1]71    CALL cpu_log( log_point(31), 'data_output_spectra', 'start' )
72
73!
[1786]74!-- Check if user gave any levels for spectra to be calculated
75    IF ( comp_spectra_level(1) == 999999 )  RETURN
76
77!
[1]78!-- Output is only performed on PE0
79    IF ( myid == 0 )  THEN
80
81!
82!--    Open file for spectra output in NetCDF format
[1327]83       CALL check_open( 107 )
[1]84
85!
86!--    Increment the counter for number of output times
87       dosp_time_count = dosp_time_count + 1
88
89!
90!--    Update the spectra time axis
[4577]91       nc_stat = NF90_PUT_VAR( id_set_sp, id_var_time_sp,                                          &
92                               (/ time_since_reference_point /),                                   &
[1]93                               start = (/ dosp_time_count /), count = (/ 1 /) )
[1783]94       CALL netcdf_handle_error( 'data_output_spectra', 47 )
[1]95
96!
97!--    If necessary, calculate time average and reset average counter
98       IF ( average_count_sp == 0 )  THEN
[4577]99          message_string = 'no spectra data available'
100          CALL message( 'data_output_spectra', 'PA0186', 0, 0, 0, 6, 0 )
[1]101       ENDIF
102       IF ( average_count_sp /= 1 )  THEN
[1322]103          spectrum_x = spectrum_x / REAL( average_count_sp, KIND=wp )
104          spectrum_y = spectrum_y / REAL( average_count_sp, KIND=wp )
[1]105          average_count_sp = 0
106       ENDIF
107
108!
109!--    Loop over all spectra defined by the user
110       m = 1
111       DO WHILE ( data_output_sp(m) /= ' '  .AND.  m <= 10 )
112
113          SELECT CASE ( TRIM( data_output_sp(m) ) )
114
115             CASE ( 'u' )
116                pr = 1
117
118             CASE ( 'v' )
119                pr = 2
120
121             CASE ( 'w' )
122                pr = 3
123
[3421]124             CASE ( 'theta' )
[1]125                pr = 4
126
127             CASE ( 'q' )
128                pr = 5
129
[1960]130             CASE ( 's' )
131                pr = 6
132
[1]133             CASE DEFAULT
[144]134!
[4577]135!--             The DEFAULT case is reached either if the parameter data_output_sp(m) contains a
136!--             wrong character string or if the user has coded a special case in the user
137!--             interface. There, the subroutine user_spectra checks which of these two conditions
[144]138!--             applies.
139                CALL user_spectra( 'data_output', m, pr )
[1]140
141          END SELECT
142
143!
144!--       Output of spectra in NetCDF format
[1327]145!--       Output of x-spectra
146          IF ( INDEX( spectra_direction(m), 'x' ) /= 0 ) THEN
147             CALL output_spectra_netcdf( m, 'x' )
148          ENDIF
[1]149!
[1327]150!--       Output of y-spectra
151          IF ( INDEX( spectra_direction(m), 'y' ) /= 0 ) THEN
152             CALL output_spectra_netcdf( m, 'y' )
[1]153          ENDIF
154
155!
156!--       Increase counter for next spectrum
157          m = m + 1
158
159       ENDDO
160
161!
162!--    Reset spectra values
[1353]163       spectrum_x = 0.0_wp; spectrum_y = 0.0_wp
[1]164
165    ENDIF
166
167    CALL cpu_log( log_point(31), 'data_output_spectra', 'stop' )
168
169#if defined( __parallel )
170!    CALL MPI_BARRIER( comm2d, ierr )  ! really necessary
171#endif
172
173#endif
174 END SUBROUTINE data_output_spectra
175
176
[4577]177!--------------------------------------------------------------------------------------------------!
[1682]178! Description:
179! ------------
180!> @todo Missing subroutine description.
[4577]181!--------------------------------------------------------------------------------------------------!
[1]182 SUBROUTINE output_spectra_netcdf( nsp, direction )
183#if defined( __netcdf )
184
[4577]185    USE basic_constants_and_equations_mod,                                                         &
[1320]186        ONLY:  pi
187
[4577]188    USE grid_variables,                                                                            &
[1320]189        ONLY:  dx, dy
190
[4577]191    USE indices,                                                                                   &
[1320]192        ONLY:  nx, ny
193
194    USE kinds
195
[1783]196    USE NETCDF
[1]197
[4577]198    USE netcdf_interface,                                                                          &
199        ONLY:  id_set_sp, id_var_dospx, id_var_dospy, nc_stat, netcdf_handle_error
[1783]200
[4577]201    USE spectra_mod,                                                                               &
[1833]202        ONLY:  dosp_time_count, n_sp_x, n_sp_y, spectrum_x, spectrum_y
[1320]203
204
[1]205    IMPLICIT NONE
206
[3547]207    CHARACTER (LEN=1), INTENT(IN) ::  direction     !< directio of spectra evaluation
[1]208
[3547]209    INTEGER(iwp), INTENT(IN)      ::  nsp           !< number of spectrum
[1]210
[3547]211    INTEGER(iwp)                  ::  i             !< running index in frequency space
212    INTEGER(iwp)                  ::  k             !< running index over number of spectrum
[1]213
[3547]214    REAL(wp)                      ::  frequency     !< wavenumber
[1]215
[3547]216    REAL(wp), DIMENSION(nx/2)     ::  netcdf_data_x !< normalized wavenumber along x written into NetCDF file
217    REAL(wp), DIMENSION(ny/2)     ::  netcdf_data_y !< normalized wavenumber along y written into NetCDF file
[1]218
219
220    IF ( direction == 'x' )  THEN
221
222       DO  k = 1, n_sp_x
223
224          DO  i = 1, nx/2
[1353]225             frequency = 2.0_wp * pi * i / ( dx * ( nx + 1 ) )
[1]226             netcdf_data_x(i) = frequency * spectrum_x(i,k,nsp)
227          ENDDO
228
[4577]229          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospx(nsp), netcdf_data_x,                     &
230                                  start = (/ 1, k, dosp_time_count /),                             &
[1]231                                  count = (/ nx/2, 1, 1 /) )
[1783]232          CALL netcdf_handle_error( 'data_output_spectra', 348 )
[1]233
234       ENDDO
235
236    ENDIF
237
238    IF ( direction == 'y' )  THEN
239
240       DO  k = 1, n_sp_y
241
242          DO  i = 1, ny/2
[1353]243             frequency = 2.0_wp * pi * i / ( dy * ( ny + 1 ) )
[1]244             netcdf_data_y(i) = frequency * spectrum_y(i,k,nsp)
245          ENDDO
246
[4577]247          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospy(nsp), netcdf_data_y,                     &
248                                  start = (/ 1, k, dosp_time_count /),                             &
[1]249                                  count = (/ ny/2, 1, 1 /) )
[1783]250          CALL netcdf_handle_error( 'data_output_spectra', 349 )
[1]251
252       ENDDO
253
254    ENDIF
255
256#endif
[4577]257 END SUBROUTINE output_spectra_netcdf
Note: See TracBrowser for help on using the repository browser.