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

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

last commit documented

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