Ignore:
Timestamp:
Jun 29, 2020 12:36:47 PM (4 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

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

    r4360 r4583  
    11!> @file data_output_tseries.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.
     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.
    98!
    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.
     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.
    1312!
    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/>.
     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! unused format removed
     
    3638! Description:
    3739! ------------
    38 !> Time series output for PROFIL. Always all time series are stored. A selection
    39 !> can be applied via the PROFIL-parameters in close_file.
    40 !------------------------------------------------------------------------------!
     40!> Time series output for PROFIL. Always all time series are stored. A selection can be applied via
     41!> the PROFIL-parameters in close_file.
     42!--------------------------------------------------------------------------------------------------!
    4143 SUBROUTINE data_output_tseries
    42  
    4344
    44     USE control_parameters,                                                    &
     45
     46    USE control_parameters,                                                                        &
    4547        ONLY:  dots_time_count, time_since_reference_point
    4648
    47     USE cpulog,                                                                &
    48         ONLY:  cpu_log, log_point 
     49    USE cpulog,                                                                                    &
     50        ONLY:  cpu_log, log_point
    4951
    5052    USE kinds
     
    5355    USE NETCDF
    5456#endif
    55     USE netcdf_interface,                                                      &
    56         ONLY:  dots_num, id_set_ts, id_var_dots, id_var_time_ts, nc_stat,      &
    57                netcdf_handle_error
     57    USE netcdf_interface,                                                                          &
     58        ONLY:  dots_num, id_set_ts, id_var_dots, id_var_time_ts, nc_stat, netcdf_handle_error
    5859
    5960    USE pegrid
    6061
    6162    USE profil_parameter
    62    
    63     USE statistics,                                                            &
     63
     64    USE statistics,                                                                                &
    6465        ONLY:  flow_statistics_called, statistic_regions, ts_value
    6566
     
    8485!--    Open file for time series output in NetCDF format
    8586       CALL check_open( 105 )
    86        
     87
    8788!--    Increment the counter for number of output times
    88 !      CAUTION: The following line has to be after the call of the subroutine
    89 !               check_open, since check_open resets the counter dots_time_count
    90 !               to 0, if a new file is opened
     89!--    CAUTION: The following line has to be after the call of the subroutine check_open, since
     90!--             check_open resets the counter dots_time_count to 0, if a new file is opened
    9191       dots_time_count = dots_time_count + 1
    92        
     92
    9393#if defined( __netcdf )
    9494!
    9595!--    Update the time series time axis
    96        nc_stat = NF90_PUT_VAR( id_set_ts, id_var_time_ts,        &
    97                                (/ time_since_reference_point /), &
    98                                start = (/ dots_time_count /),    &
     96       nc_stat = NF90_PUT_VAR( id_set_ts, id_var_time_ts,                                          &
     97                               (/ time_since_reference_point /),                                   &
     98                               start = (/ dots_time_count /),                                      &
    9999                               count = (/ 1 /) )
    100100       CALL netcdf_handle_error( 'data_output_tseries', 350 )
     
    108108#if defined( __netcdf )
    109109          DO  i = 1, dots_num
    110              nc_stat = NF90_PUT_VAR( id_set_ts, id_var_dots(i,sr),  &
    111                                      (/ ts_value(i,sr) /),          &
    112                                      start = (/ dots_time_count /), &
     110             nc_stat = NF90_PUT_VAR( id_set_ts, id_var_dots(i,sr),                                 &
     111                                     (/ ts_value(i,sr) /),                                         &
     112                                     start = (/ dots_time_count /),                                &
    113113                                     count = (/ 1 /) )
    114114             CALL netcdf_handle_error( 'data_output_tseries', 351 )
Note: See TracChangeset for help on using the changeset viewer.