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

Last change on this file since 4180 was 4180, checked in by scharf, 5 years ago

removed comments in 'Former revisions' section that are older than 01.01.2019

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