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

Last change on this file since 4360 was 4360, checked in by suehring, 4 years ago

Bugfix in output of time-averaged plant-canopy quanities; Output of plant-canopy data only where tall canopy is defined; land-surface model: fix wrong location strings; tests: update urban test case; all source code files: copyright update

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