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

Last change on this file since 3842 was 3655, checked in by knoop, 5 years ago

Bugfix: made "unit" and "found" intend INOUT in module interface subroutines + automatic copyright update

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