Ignore:
Timestamp:
Jun 11, 2020 8:51:48 AM (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/cpulog_mod.f90

    r4549 r4559  
    11!> @file cpulog_mod.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
     
    2524! -----------------
    2625! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4549 2020-05-29 09:27:29Z raasch
    2729! bugfix for r4539: values for min/max/rms stored in separate arrays
    28 ! 
     30!
    2931! 4539 2020-05-18 14:05:17Z raasch
    3032! code re-structured,
    3133! cpu time per grid point and timestep does not included initialization and spinup any more
    32 ! 
     34!
    3335! 4536 2020-05-17 17:24:13Z raasch
    3436! restart I/O transfer speed added
    35 ! 
     37!
    3638! 4429 2020-02-27 15:24:30Z raasch
    3739! bugfix: cpp-directives added for serial mode
    38 ! 
     40!
    3941! 4378 2020-01-16 13:22:48Z Giersch
    4042! Format of rms output changed to allow values >= 100
    41 ! 
     43!
    4244! 4360 2020-01-07 11:25:50Z suehring
    4345! Corrected "Former revisions" section
    44 ! 
     46!
    4547! 4015 2019-06-05 13:25:35Z raasch
    46 ! all reals changed to double precision in order to work with 32-bit working precision,
    47 ! otherwise calculated time intervals would mostly give zero
    48 ! 
     48! all reals changed to double precision in order to work with 32-bit working precision, otherwise
     49! calculated time intervals would mostly give zero
     50!
    4951! 3885 2019-04-11 11:29:34Z kanani
    50 ! Changes related to global restructuring of location messages and introduction
    51 ! of additional debug messages
    52 ! 
     52! Changes related to global restructuring of location messages and introduction of additional debug
     53! messages
     54!
    5355! 3655 2019-01-07 16:51:22Z knoop
    5456! output format limited to a maximum line length of 80
     
    6062! Description:
    6163! ------------
    62 !> CPU-time measurements for any program part whatever. Results of the
    63 !> measurements are output at the end of the run in local file CPU_MEASURES.
    64 !>
    65 !> To measure the CPU-time (better to say the wallclock time) of a specific code
    66 !> segment, two calls of cpu_log have to be used as brackets in front and at the
    67 !> end of the segment:
     64!> CPU-time measurements for any program part whatever. Results of the measurements are output at
     65!> the end of the run in local file CPU_MEASURES.
     66!>
     67!> To measure the CPU-time (better to say the wallclock time) of a specific code segment, two calls
     68!> of cpu_log have to be used as brackets in front and at the end of the segment:
    6869!>
    6970!>     CALL cpu_log( log_point(n), 'any identifier', 'start' )
     
    7172!>     CALL cpu_log( log_point(n), 'any identifier', 'stop' )
    7273!>
    73 !> Parts of the code segment can be excluded from the measurement by additional
    74 !> call of cpu_log:
     74!> Parts of the code segment can be excluded from the measurement by additional call of cpu_log:
    7575!>
    7676!>       ... first segment to be measured
     
    8080!>       ... second segment to be mesasured
    8181!>
    82 !> n is an INTEGER within the interval [1,100] defining the id of the specific
    83 !> code segment, 'any identifier' is a string describing the code segment to be
    84 !> measured. It can be freely chosen and results will appear under this name in
    85 !> file CPU_MEASURES. ids can only be used once. If you like to do a
    86 !> measurement of a new part of the code, please look for an id which is unused
    87 !> ao far.
    88 !>
    89 !> runtime_parameters-parameter cpu_log_barrierwait can be used to set an MPI
    90 !> barrier at the beginning of the measurement (modus 'start' or 'continue'),
    91 !> to avoid that idle times (due to MPI calls in the code segment, which are
    92 !> waiting for other processes to be finished) affect the measurements.
     82!> n is an INTEGER within the interval [1,100] defining the id of the specific code segment,
     83!> 'any identifier' is a string describing the code segment to be measured. It can be freely chosen
     84!> and results will appear under this name in file CPU_MEASURES. ids can only be used once. If you
     85!> like to do a measurement of a new part of the code, please look for an id which is unused so far.
     86!>
     87!> runtime_parameters-parameter cpu_log_barrierwait can be used to set an MPI barrier at the
     88!> beginning of the measurement (modus 'start' or 'continue'), to avoid that idle times (due to MPI
     89!> calls in the code segment, which are waiting for other processes to be finished) affect the
     90!> measurements.
    9391!> If barriers shall not be used at all, a fourth, optional parameter has to be
    9492!> given:
     
    9694!>     CALL cpu_log( ..., ..., 'start', cpu_log_nowait )
    9795!>
    98 !> Variable log_point should be used for non-overlapping code segments, and they
    99 !> should sum up to the total cpu-time required by the complete run.
     96!> Variable log_point should be used for non-overlapping code segments, and they should sum up to
     97!> the total cpu-time required by the complete run.
    10098!> Variable log_point_s can be used for any other special (s) measurements.
    101 !------------------------------------------------------------------------------!
     99!--------------------------------------------------------------------------------------------------!
    102100 MODULE cpulog
    103  
     101
    104102
    105103    USE control_parameters,                                                                        &
    106104        ONLY: message_string, nr_timesteps_this_run, restart_data_format_output,                   &
    107105              restart_file_size, run_description_header, synchronous_exchange, write_binary
    108                
     106
    109107    USE indices,                                                                                   &
    110108        ONLY: ngp_3d, nx, ny, nz
    111        
     109
    112110    USE kinds
    113    
     111
    114112    USE pegrid
    115113
     
    128126    END INTERFACE cpu_statistics
    129127
    130     INTEGER(iwp), PARAMETER ::  cpu_log_continue = 0  !< 
    131     INTEGER(iwp), PARAMETER ::  cpu_log_pause = 1     !< 
    132     INTEGER(iwp), PARAMETER ::  cpu_log_start = 2     !< 
    133     INTEGER(iwp), PARAMETER ::  cpu_log_stop = 3      !< 
    134 
    135     LOGICAL            ::  cpu_log_barrierwait = .FALSE.  !< 
    136     LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.       !< 
     128    INTEGER(iwp), PARAMETER ::  cpu_log_continue = 0  !<
     129    INTEGER(iwp), PARAMETER ::  cpu_log_pause = 1     !<
     130    INTEGER(iwp), PARAMETER ::  cpu_log_start = 2     !<
     131    INTEGER(iwp), PARAMETER ::  cpu_log_stop = 3      !<
     132
     133    LOGICAL            ::  cpu_log_barrierwait = .FALSE.  !<
     134    LOGICAL, PARAMETER ::  cpu_log_nowait = .FALSE.       !<
    137135
    138136    REAL(dp) ::  initial_wallclock_time  !<
     
    146144       REAL(dp)           ::  sum        !<
    147145       REAL(dp)           ::  vector     !<
    148        INTEGER(iwp)       ::  counts     !< 
    149        CHARACTER (LEN=25) ::  place      !< 
     146       INTEGER(iwp)       ::  counts     !<
     147       CHARACTER (LEN=25) ::  place      !<
    150148    END TYPE logpoint
    151149
     
    168166       IMPLICIT NONE
    169167
    170        CHARACTER (LEN=*) ::  modus              !< 
    171        CHARACTER (LEN=*) ::  place              !< 
    172        
    173        LOGICAL           ::  wait_allowed       !< 
    174        LOGICAL, OPTIONAL ::  barrierwait        !< 
    175        LOGICAL, SAVE     ::  first = .TRUE.     !< 
    176        
     168       CHARACTER (LEN=*) ::  modus              !<
     169       CHARACTER (LEN=*) ::  place              !<
     170
     171       LOGICAL           ::  wait_allowed       !<
     172       LOGICAL, OPTIONAL ::  barrierwait        !<
     173       LOGICAL, SAVE     ::  first = .TRUE.     !<
     174
    177175       REAL(dp)          ::  mtime = 0.0_dp     !<
    178176       REAL(dp)          ::  mtimevec = 0.0_dp  !<
    179        TYPE(logpoint)    ::  log_event          !< 
    180 
    181        INTEGER(idp)     ::  count        !< 
    182        INTEGER(idp)     ::  count_rate   !< 
     177       TYPE(logpoint)    ::  log_event          !<
     178
     179       INTEGER(idp)     ::  count        !<
     180       INTEGER(idp)     ::  count_rate   !<
    183181
    184182
     
    270268!> and output on PE0.
    271269!------------------------------------------------------------------------------!
    272  
     270
    273271    SUBROUTINE cpu_statistics
    274272
    275273       IMPLICIT NONE
    276274
    277        INTEGER(iwp)    ::  i               !< 
    278        INTEGER(iwp)    ::  ii(1)           !< 
     275       INTEGER(iwp)    ::  i               !<
     276       INTEGER(iwp)    ::  ii(1)           !<
    279277#if defined( __parallel )
    280        INTEGER(iwp)    ::  iii             !< 
     278       INTEGER(iwp)    ::  iii             !<
    281279       INTEGER(iwp)    ::  sender          !<
    282280#endif
Note: See TracChangeset for help on using the changeset viewer.