Ignore:
Timestamp:
Jul 6, 2020 3:56:08 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/run_control.f90

    r4360 r4591  
    11!> @file run_control.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!--------------------------------------------------------------------------------------------------!
     18!
    1919!
    2020! Current revisions:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! File re-formatted to follow the PALM coding standard
     28!
     29!
     30! 4360 2020-01-07 11:25:50Z suehring
    2731! Corrected "Former revisions" section
    28 ! 
     32!
    2933! 3655 2019-01-07 16:51:22Z knoop
    3034! Corrected "Former revisions" section
     
    3741! ------------
    3842!> Computation and output of run-control quantities
    39 !------------------------------------------------------------------------------!
     43!--------------------------------------------------------------------------------------------------!
    4044 SUBROUTINE run_control
    41  
    4245
    43     USE cpulog,                                                                &
    44         ONLY:  cpu_log, log_point
    4546
    46     USE control_parameters,                                                    &
    47         ONLY:  advected_distance_x, advected_distance_y,                       &
    48                current_timestep_number, disturbance_created, dt_3d, mgcycles,  &
    49                run_control_header, runnr, simulated_time, simulated_time_chr,  &
     47    USE cpulog,                                                                                    &
     48        ONLY:  cpu_log,                                                                            &
     49               log_point
     50
     51    USE control_parameters,                                                                        &
     52        ONLY:  advected_distance_x,                                                                &
     53               advected_distance_y,                                                                &
     54               current_timestep_number,                                                            &
     55               disturbance_created,                                                                &
     56               dt_3d,                                                                              &
     57               mgcycles,                                                                           &
     58               run_control_header,                                                                 &
     59               runnr,                                                                              &
     60               simulated_time,                                                                     &
     61               simulated_time_chr,                                                                 &
    5062               timestep_reason
    5163
    52     USE indices,                                                               &
     64    USE indices,                                                                                   &
    5365        ONLY:  nzb
    5466
     
    5769    USE pegrid
    5870
    59     USE statistics,                                                            &
    60         ONLY:  flow_statistics_called, hom, pr_palm, u_max, u_max_ijk, v_max,  &
    61                v_max_ijk, w_max, w_max_ijk
     71    USE statistics,                                                                                &
     72        ONLY:  flow_statistics_called,                                                             &
     73               hom,                                                                                &
     74               pr_palm,                                                                            &
     75               u_max,                                                                              &
     76               u_max_ijk,                                                                          &
     77               v_max,                                                                              &
     78               v_max_ijk,                                                                          &
     79               w_max,                                                                              &
     80               w_max_ijk
    6281
    6382    IMPLICIT NONE
    6483
    65     CHARACTER (LEN=1) ::  disturb_chr
     84    CHARACTER (LEN=1) ::  disturb_chr  !<
    6685
    6786!
     
    7897
    7998!
    80 !--    Check, whether file unit is already open (may have been opened in header
    81 !--    before)
     99!--    Check, whether file unit is already open (may have been opened in header before)
    82100       CALL check_open( 15 )
    83101
     
    96114          disturb_chr = ' '
    97115       ENDIF
    98        WRITE ( 15, 101 )  runnr, current_timestep_number, simulated_time_chr,  &
    99                           INT( ( simulated_time-INT( simulated_time ) ) * 100),&
    100                           dt_3d, timestep_reason, u_max, disturb_chr,          &
    101                           v_max, disturb_chr, w_max, hom(nzb,1,pr_palm,0),     &
    102                           hom(nzb+8,1,pr_palm,0), hom(nzb+3,1,pr_palm,0),      &
    103                           hom(nzb+6,1,pr_palm,0), hom(nzb+4,1,pr_palm,0),      &
    104                           hom(nzb+5,1,pr_palm,0), hom(nzb+9,1,pr_palm,0),      &
    105                           hom(nzb+10,1,pr_palm,0), u_max_ijk(1:3),             &
    106                           v_max_ijk(1:3), w_max_ijk(1:3),                      &
    107                           advected_distance_x/1000.0_wp,                       &
     116       WRITE ( 15, 101 )  runnr, current_timestep_number, simulated_time_chr,                      &
     117                          INT( ( simulated_time-INT( simulated_time ) ) * 100),                    &
     118                          dt_3d, timestep_reason, u_max, disturb_chr, v_max, disturb_chr, w_max,   &
     119                          hom(nzb,1,pr_palm,0), hom(nzb+8,1,pr_palm,0), hom(nzb+3,1,pr_palm,0),    &
     120                          hom(nzb+6,1,pr_palm,0), hom(nzb+4,1,pr_palm,0), hom(nzb+5,1,pr_palm,0),  &
     121                          hom(nzb+9,1,pr_palm,0), hom(nzb+10,1,pr_palm,0), u_max_ijk(1:3),         &
     122                          v_max_ijk(1:3), w_max_ijk(1:3), advected_distance_x/1000.0_wp,           &
    108123                          advected_distance_y/1000.0_wp, mgcycles
    109124!
     
    113128    ENDIF
    114129!
    115 !-- If required, reset disturbance flag. This has to be done outside the above 
     130!-- If required, reset disturbance flag. This has to be done outside the above
    116131!-- IF-loop, because the flag would otherwise only be reset on PE0
    117132    IF ( disturbance_created )  disturbance_created = .FALSE.
     
    131146          &'----------------------------------------------------------------', &
    132147          &'---------')
    133 101 FORMAT (I3,1X,I6,1X,A8,'.',I2.2,1X,F8.4,A1,1X,F8.4,A1,F8.4,A1,F8.4,1X,     &
    134             F6.3,1X,F5.2, &
     148101 FORMAT (I3,1X,I6,1X,A8,'.',I2.2,1X,F8.4,A1,1X,F8.4,A1,F8.4,A1,F8.4,1X, F6.3,1X,F5.2,           &
    135149            2X,E10.3,2X,F6.0,1X,4(E10.3,1X),3(3(I4),1X),F8.3,1X,F8.3,5X,I3)
    136150
Note: See TracChangeset for help on using the changeset viewer.