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/data_log.f90

    r4360 r4559  
    11!> @file data_log.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! 3725 2019-02-07 10:11:02Z raasch
    3032! preprocessor directives removed to avoid compiler warnings
    31 ! 
     33!
    3234! 3655 2019-01-07 16:51:22Z knoop
    3335! Corrected "Former revisions" section
     
    4042! ------------
    4143!> Complete logging of data
    42 !------------------------------------------------------------------------------!
     44!--------------------------------------------------------------------------------------------------!
    4345 SUBROUTINE data_log( array, i1, i2, j1, j2, k1, k2 )
    44  
    45     USE control_parameters,                                                    &
     46
     47    USE control_parameters,                                                                        &
    4648        ONLY:  log_message, simulated_time
    47        
     49
    4850    USE kinds
    49        
     51
    5052    USE pegrid
    5153
    5254    IMPLICIT NONE
    5355
    54     INTEGER(iwp) ::  i1  !< 
    55     INTEGER(iwp) ::  i2  !< 
    56     INTEGER(iwp) ::  j1  !< 
    57     INTEGER(iwp) ::  j2  !< 
    58     INTEGER(iwp) ::  k1  !< 
    59     INTEGER(iwp) ::  k2  !< 
     56    INTEGER(iwp) ::  i1  !<
     57    INTEGER(iwp) ::  i2  !<
     58    INTEGER(iwp) ::  j1  !<
     59    INTEGER(iwp) ::  j2  !<
     60    INTEGER(iwp) ::  k1  !<
     61    INTEGER(iwp) ::  k2  !<
    6062
    61     REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) ::  array  !< 
     63    REAL(wp), DIMENSION(i1:i2,j1:j2,k1:k2) ::  array  !<
    6264
    6365
     
    8284
    8385
    84 !------------------------------------------------------------------------------!
     86!--------------------------------------------------------------------------------------------------!
    8587! Description:
    8688! ------------
    8789!> Complete logging of data for 2d arrays
    88 !------------------------------------------------------------------------------!
    89  
     90!--------------------------------------------------------------------------------------------------!
     91
    9092 SUBROUTINE data_log_2d( array, i1, i2, j1, j2)
    9193
    92     USE control_parameters,                                                    &
     94    USE control_parameters,                                                                        &
    9395        ONLY:  log_message, simulated_time
    9496
    9597    USE kinds
    96            
     98
    9799    USE pegrid
    98100
    99101    IMPLICIT NONE
    100102
    101     INTEGER(iwp) ::  i1  !< 
    102     INTEGER(iwp) ::  i2  !< 
    103     INTEGER(iwp) ::  j1  !< 
    104     INTEGER(iwp) ::  j2  !< 
     103    INTEGER(iwp) ::  i1  !<
     104    INTEGER(iwp) ::  i2  !<
     105    INTEGER(iwp) ::  j1  !<
     106    INTEGER(iwp) ::  j2  !<
    105107
    106     REAL(wp), DIMENSION(i1:i2,j1:j2) ::  array  !< 
     108    REAL(wp), DIMENSION(i1:i2,j1:j2) ::  array  !<
    107109
    108110
     
    127129
    128130
    129 !------------------------------------------------------------------------------!
     131!--------------------------------------------------------------------------------------------------!
    130132! Description:
    131133! ------------
    132134!> Complete logging of data for 2d integer arrays
    133 !------------------------------------------------------------------------------!
    134  
     135!--------------------------------------------------------------------------------------------------!
     136
    135137 SUBROUTINE data_log_2d_int( array, i1, i2, j1, j2)
    136138
    137     USE control_parameters,                                                    &
     139    USE control_parameters,                                                                        &
    138140        ONLY:  log_message, simulated_time
    139141
    140142    USE kinds
    141            
     143
    142144    USE pegrid
    143145
    144146    IMPLICIT NONE
    145147
    146     INTEGER(iwp) ::  i1  !< 
    147     INTEGER(iwp) ::  i2  !< 
    148     INTEGER(iwp) ::  j1  !< 
    149     INTEGER(iwp) ::  j2  !< 
     148    INTEGER(iwp) ::  i1  !<
     149    INTEGER(iwp) ::  i2  !<
     150    INTEGER(iwp) ::  j1  !<
     151    INTEGER(iwp) ::  j2  !<
    150152
    151     INTEGER(iwp), DIMENSION(i1:i2,j1:j2) ::  array  !< 
     153    INTEGER(iwp), DIMENSION(i1:i2,j1:j2) ::  array  !<
    152154
    153155
Note: See TracChangeset for help on using the changeset viewer.