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

Last change on this file since 2372 was 2101, checked in by suehring, 7 years ago

last commit documented

  • Property svn:keywords set to Id
File size: 9.1 KB
Line 
1!> @file data_output_spectra.f90
2!------------------------------------------------------------------------------!
3! This file is part of PALM.
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-2017 Leibniz Universitaet Hannover
18!------------------------------------------------------------------------------!
19!
20! Current revisions:
21! ------------------
22!
23!
24! Former revisions:
25! -----------------
26! $Id: data_output_spectra.f90 2101 2017-01-05 16:42:31Z sward $
27!
28! 2000 2016-08-20 18:09:15Z knoop
29! Forced header and separation lines into 80 columns
30!
31! 1960 2016-07-12 16:34:24Z suehring
32! Additional default spectra for passive scalar
33!
34! 1833 2016-04-07 14:23:03Z raasch
35! spectrum renamed spectra_mod, spectra related variables moved to spectra_mod,
36! routines data_output_spectra_x/y removed
37!
38! 1786 2016-03-08 05:49:27Z raasch
39! cpp-directives for spectra removed, immediate return if no spectra levels are
40! given
41!
42! 1783 2016-03-06 18:36:17Z raasch
43! name change of netcdf routines and module + related changes
44!
45! 1682 2015-10-07 23:56:08Z knoop
46! Code annotations made doxygen readable
47!
48! 1353 2014-04-08 15:21:23Z heinze
49! REAL constants provided with KIND-attribute
50!
51! 1327 2014-03-21 11:00:16Z raasch
52! -netcdf output queries
53!
54! 1324 2014-03-21 09:13:16Z suehring
55! Bugfix: module statistics and module spectrum added, missing variables in ONLY
56! arguments added
57!
58! 1322 2014-03-20 16:38:49Z raasch
59! REAL functions provided with KIND-attribute
60!
61! 1320 2014-03-20 08:40:49Z raasch
62! ONLY-attribute added to USE-statements,
63! kind-parameters added to all INTEGER and REAL declaration statements,
64! kinds are defined in new module kinds,
65! revision history before 2012 removed,
66! comment fields (!:) to be used for variable explanations added to
67! all variable declaration statements
68!
69! 1318 2014-03-17 13:35:16Z raasch
70! module interfaces removed
71!
72! 1036 2012-10-22 13:43:42Z raasch
73! code put under GPL (PALM 3.9)
74!
75! 964 2012-07-26 09:14:24Z raasch
76! code for profil-output removed
77!
78! Revision 1.1  2001/01/05 15:14:20  raasch
79! Initial revision
80!
81!
82! Description:
83! ------------
84!> Writing spectra data on file, using a special format which allows
85!> plotting of these data with PROFIL-graphic-software
86!------------------------------------------------------------------------------!
87 SUBROUTINE data_output_spectra
88 
89#if defined( __netcdf )
90    USE control_parameters,                                                    &
91        ONLY:  message_string, run_description_header,                         &
92               time_since_reference_point
93
94    USE cpulog,                                                                &
95        ONLY:  cpu_log, log_point
96
97    USE kinds
98
99    USE NETCDF
100
101    USE netcdf_interface,                                                      &
102        ONLY:  id_set_sp, id_var_time_sp, nc_stat, netcdf_handle_error
103
104    USE pegrid
105
106    USE spectra_mod,                                                           &
107        ONLY:  average_count_sp, averaging_interval_sp, comp_spectra_level,    &
108               data_output_sp, dosp_time_count, spectra_direction, spectrum_x, &
109               spectrum_y
110
111
112    IMPLICIT NONE
113
114    INTEGER(iwp) ::  cranz_x !<
115    INTEGER(iwp) ::  cranz_y !<
116    INTEGER(iwp) ::  m       !<
117    INTEGER(iwp) ::  pr      !<
118   
119    LOGICAL      ::  frame_x !<
120    LOGICAL      ::  frame_y !<
121
122    CALL cpu_log( log_point(31), 'data_output_spectra', 'start' )
123
124!
125!-- Check if user gave any levels for spectra to be calculated
126    IF ( comp_spectra_level(1) == 999999 )  RETURN
127
128!
129!-- Output is only performed on PE0
130    IF ( myid == 0 )  THEN
131
132!
133!--    Open file for spectra output in NetCDF format
134       CALL check_open( 107 )
135
136!
137!--    Increment the counter for number of output times
138       dosp_time_count = dosp_time_count + 1
139
140!
141!--    Update the spectra time axis
142       nc_stat = NF90_PUT_VAR( id_set_sp, id_var_time_sp,        &
143                               (/ time_since_reference_point /), &
144                               start = (/ dosp_time_count /), count = (/ 1 /) )
145       CALL netcdf_handle_error( 'data_output_spectra', 47 )
146
147!
148!--    If necessary, calculate time average and reset average counter
149       IF ( average_count_sp == 0 )  THEN
150           message_string = 'no spectra data available'
151           CALL message( 'data_output_spectra', 'PA0186', 0, 0, 0, 6, 0 )
152       ENDIF
153       IF ( average_count_sp /= 1 )  THEN
154          spectrum_x = spectrum_x / REAL( average_count_sp, KIND=wp )
155          spectrum_y = spectrum_y / REAL( average_count_sp, KIND=wp )
156          average_count_sp = 0
157       ENDIF
158
159!
160!--    Loop over all spectra defined by the user
161       m = 1
162       DO WHILE ( data_output_sp(m) /= ' '  .AND.  m <= 10 )
163
164          SELECT CASE ( TRIM( data_output_sp(m) ) )
165
166             CASE ( 'u' )
167                pr = 1
168
169             CASE ( 'v' )
170                pr = 2
171
172             CASE ( 'w' )
173                pr = 3
174
175             CASE ( 'pt' )
176                pr = 4
177
178             CASE ( 'q' )
179                pr = 5
180
181             CASE ( 's' )
182                pr = 6
183
184             CASE DEFAULT
185!
186!--             The DEFAULT case is reached either if the parameter
187!--             data_output_sp(m) contains a wrong character string or if the
188!--             user has coded a special case in the user interface. There, the
189!--             subroutine user_spectra checks which of these two conditions
190!--             applies.
191                CALL user_spectra( 'data_output', m, pr )
192
193          END SELECT
194
195!
196!--       Output of spectra in NetCDF format
197!--       Output of x-spectra
198          IF ( INDEX( spectra_direction(m), 'x' ) /= 0 ) THEN
199             CALL output_spectra_netcdf( m, 'x' )
200          ENDIF
201!
202!--       Output of y-spectra
203          IF ( INDEX( spectra_direction(m), 'y' ) /= 0 ) THEN
204             CALL output_spectra_netcdf( m, 'y' )
205          ENDIF
206
207!
208!--       Increase counter for next spectrum
209          m = m + 1
210
211       ENDDO
212
213!
214!--    Reset spectra values
215       spectrum_x = 0.0_wp; spectrum_y = 0.0_wp
216
217    ENDIF
218
219    CALL cpu_log( log_point(31), 'data_output_spectra', 'stop' )
220
221#if defined( __parallel )
222!    CALL MPI_BARRIER( comm2d, ierr )  ! really necessary
223#endif
224
225#endif
226 END SUBROUTINE data_output_spectra
227
228
229!------------------------------------------------------------------------------!
230! Description:
231! ------------
232!> @todo Missing subroutine description.
233!------------------------------------------------------------------------------!
234 SUBROUTINE output_spectra_netcdf( nsp, direction )
235#if defined( __netcdf )
236
237    USE constants,                                                             &
238        ONLY:  pi
239
240    USE grid_variables,                                                        &
241        ONLY:  dx, dy
242
243    USE indices,                                                               &
244        ONLY:  nx, ny
245
246    USE kinds
247
248    USE NETCDF
249
250    USE netcdf_interface,                                                      &
251        ONLY:  id_set_sp, id_var_dospx, id_var_dospy, nc_stat,                 &
252               netcdf_handle_error
253
254    USE spectra_mod,                                                           &
255        ONLY:  dosp_time_count, n_sp_x, n_sp_y, spectrum_x, spectrum_y
256
257
258    IMPLICIT NONE
259
260    CHARACTER (LEN=1), INTENT(IN) ::  direction     !<
261
262    INTEGER(iwp), INTENT(IN)      ::  nsp           !<
263
264    INTEGER(iwp)                  ::  i             !<
265    INTEGER(iwp)                  ::  k             !<
266
267    REAL(wp)                      ::  frequency     !<
268
269    REAL(wp), DIMENSION(nx/2)     ::  netcdf_data_x !<
270    REAL(wp), DIMENSION(ny/2)     ::  netcdf_data_y !<
271
272
273    IF ( direction == 'x' )  THEN
274
275       DO  k = 1, n_sp_x
276
277          DO  i = 1, nx/2
278             frequency = 2.0_wp * pi * i / ( dx * ( nx + 1 ) )
279             netcdf_data_x(i) = frequency * spectrum_x(i,k,nsp)
280          ENDDO
281
282          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospx(nsp), netcdf_data_x, &
283                                  start = (/ 1, k, dosp_time_count /), &
284                                  count = (/ nx/2, 1, 1 /) )
285          CALL netcdf_handle_error( 'data_output_spectra', 348 )
286
287       ENDDO
288
289    ENDIF
290
291    IF ( direction == 'y' )  THEN
292
293       DO  k = 1, n_sp_y
294
295          DO  i = 1, ny/2
296             frequency = 2.0_wp * pi * i / ( dy * ( ny + 1 ) )
297             netcdf_data_y(i) = frequency * spectrum_y(i,k,nsp)
298          ENDDO
299
300          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospy(nsp), netcdf_data_y, &
301                                  start = (/ 1, k, dosp_time_count /), &
302                                  count = (/ ny/2, 1, 1 /) )
303          CALL netcdf_handle_error( 'data_output_spectra', 349 )
304
305       ENDDO
306
307    ENDIF
308
309#endif
310 END SUBROUTINE output_spectra_netcdf
Note: See TracBrowser for help on using the repository browser.