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

Last change on this file since 1960 was 1960, checked in by suehring, 8 years ago

Separate balance equations for humidity and passive_scalar

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