Ignore:
Timestamp:
Jun 25, 2020 9:53:58 AM (4 years ago)
Author:
raasch
Message:

further re-formatting to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/data_output_spectra.f90

    r4360 r4577  
    11!> @file data_output_spectra.f90
    2 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    33! This file is part of the PALM model system.
    44!
    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/>.
     5! PALM is free software: you can redistribute it and/or modify it under the terms of the GNU General
     6! Public License as published by the Free Software Foundation, either version 3 of the License, or
     7! (at your option) any later version.
     8!
     9! PALM is distributed in the hope that it will be useful, but WITHOUT ANY WARRANTY; without even the
     10! implied warranty of MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU General
     11! Public License for more details.
     12!
     13! You should have received a copy of the GNU General Public License along with PALM. If not, see
     14! <http://www.gnu.org/licenses/>.
    1615!
    1716! Copyright 1997-2020 Leibniz Universitaet Hannover
    18 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4360 2020-01-07 11:25:50Z suehring
    2729! Corrected "Former revisions" section
    28 ! 
     30!
    2931! 3655 2019-01-07 16:51:22Z knoop
    3032! variables documented
     
    3840!> Writing spectra data on file, using a special format which allows
    3941!> plotting of these data with PROFIL-graphic-software
    40 !------------------------------------------------------------------------------!
     42!--------------------------------------------------------------------------------------------------!
    4143 SUBROUTINE data_output_spectra
    42  
     44
    4345#if defined( __netcdf )
    44     USE control_parameters,                                                    &
     46    USE control_parameters,                                                                        &
    4547        ONLY:  message_string, time_since_reference_point
    4648
    47     USE cpulog,                                                                &
     49    USE cpulog,                                                                                    &
    4850        ONLY:  cpu_log, log_point
    4951
     
    5254    USE NETCDF
    5355
    54     USE netcdf_interface,                                                      &
     56    USE netcdf_interface,                                                                          &
    5557        ONLY:  id_set_sp, id_var_time_sp, nc_stat, netcdf_handle_error
    5658
    5759    USE pegrid
    5860
    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
     61    USE spectra_mod,                                                                               &
     62        ONLY:  average_count_sp, averaging_interval_sp, comp_spectra_level, data_output_sp,        &
     63               dosp_time_count, spectra_direction, spectrum_x, spectrum_y
    6364
    6465
     
    6768    INTEGER(iwp) ::  m       !< running index over spectra output
    6869    INTEGER(iwp) ::  pr      !< index used to assign default quantities to data output
    69    
     70
    7071    CALL cpu_log( log_point(31), 'data_output_spectra', 'start' )
    7172
     
    8889!
    8990!--    Update the spectra time axis
    90        nc_stat = NF90_PUT_VAR( id_set_sp, id_var_time_sp,        &
    91                                (/ time_since_reference_point /), &
     91       nc_stat = NF90_PUT_VAR( id_set_sp, id_var_time_sp,                                          &
     92                               (/ time_since_reference_point /),                                   &
    9293                               start = (/ dosp_time_count /), count = (/ 1 /) )
    9394       CALL netcdf_handle_error( 'data_output_spectra', 47 )
     
    9697!--    If necessary, calculate time average and reset average counter
    9798       IF ( average_count_sp == 0 )  THEN
    98            message_string = 'no spectra data available'
    99            CALL message( 'data_output_spectra', 'PA0186', 0, 0, 0, 6, 0 )
     99          message_string = 'no spectra data available'
     100          CALL message( 'data_output_spectra', 'PA0186', 0, 0, 0, 6, 0 )
    100101       ENDIF
    101102       IF ( average_count_sp /= 1 )  THEN
     
    132133             CASE DEFAULT
    133134!
    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
     135!--             The DEFAULT case is reached either if the parameter data_output_sp(m) contains a
     136!--             wrong character string or if the user has coded a special case in the user
     137!--             interface. There, the subroutine user_spectra checks which of these two conditions
    138138!--             applies.
    139139                CALL user_spectra( 'data_output', m, pr )
     
    175175
    176176
    177 !------------------------------------------------------------------------------!
     177!--------------------------------------------------------------------------------------------------!
    178178! Description:
    179179! ------------
    180180!> @todo Missing subroutine description.
    181 !------------------------------------------------------------------------------!
     181!--------------------------------------------------------------------------------------------------!
    182182 SUBROUTINE output_spectra_netcdf( nsp, direction )
    183183#if defined( __netcdf )
    184184
    185     USE basic_constants_and_equations_mod,                                     &
     185    USE basic_constants_and_equations_mod,                                                         &
    186186        ONLY:  pi
    187187
    188     USE grid_variables,                                                        &
     188    USE grid_variables,                                                                            &
    189189        ONLY:  dx, dy
    190190
    191     USE indices,                                                               &
     191    USE indices,                                                                                   &
    192192        ONLY:  nx, ny
    193193
     
    196196    USE NETCDF
    197197
    198     USE netcdf_interface,                                                      &
    199         ONLY:  id_set_sp, id_var_dospx, id_var_dospy, nc_stat,                 &
    200                netcdf_handle_error
    201 
    202     USE spectra_mod,                                                           &
     198    USE netcdf_interface,                                                                          &
     199        ONLY:  id_set_sp, id_var_dospx, id_var_dospy, nc_stat, netcdf_handle_error
     200
     201    USE spectra_mod,                                                                               &
    203202        ONLY:  dosp_time_count, n_sp_x, n_sp_y, spectrum_x, spectrum_y
    204203
     
    228227          ENDDO
    229228
    230           nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospx(nsp), netcdf_data_x, &
    231                                   start = (/ 1, k, dosp_time_count /), &
     229          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospx(nsp), netcdf_data_x,                     &
     230                                  start = (/ 1, k, dosp_time_count /),                             &
    232231                                  count = (/ nx/2, 1, 1 /) )
    233232          CALL netcdf_handle_error( 'data_output_spectra', 348 )
     
    246245          ENDDO
    247246
    248           nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospy(nsp), netcdf_data_y, &
    249                                   start = (/ 1, k, dosp_time_count /), &
     247          nc_stat = NF90_PUT_VAR( id_set_sp, id_var_dospy(nsp), netcdf_data_y,                     &
     248                                  start = (/ 1, k, dosp_time_count /),                             &
    250249                                  count = (/ ny/2, 1, 1 /) )
    251250          CALL netcdf_handle_error( 'data_output_spectra', 349 )
Note: See TracChangeset for help on using the changeset viewer.