Ignore:
Timestamp:
Aug 25, 2020 7:52:08 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/init_slope.f90

    r4360 r4648  
    11!> @file init_slope.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:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former 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! Modularization of all bulk cloud physics code components
     
    3638! Description:
    3739! ------------
    38 !> Initialization of the temperature field and other variables used in case
    39 !> of a sloping surface.
     40!> Initialization of the temperature field and other variables used in case of a sloping surface.
    4041!> @note when a sloping surface is used, only one constant temperature
    4142!>       gradient is allowed!
    42 !------------------------------------------------------------------------------!
     43!--------------------------------------------------------------------------------------------------!
    4344 SUBROUTINE init_slope
    44  
    4545
    46     USE arrays_3d,                                                             &
     46
     47    USE arrays_3d,                                                                                 &
    4748        ONLY:  pt, pt_init, pt_slope_ref, zu
    48        
    49     USE basic_constants_and_equations_mod,                                     &
     49
     50    USE basic_constants_and_equations_mod,                                                         &
    5051        ONLY:  pi
    51                    
    52     USE control_parameters,                                                    &
    53         ONLY:  alpha_surface, initializing_actions, pt_slope_offset,           &
    54                pt_surface, pt_vertical_gradient, sin_alpha_surface
    55        
    56     USE grid_variables,                                                        &
     52
     53    USE control_parameters,                                                                        &
     54        ONLY:  alpha_surface, initializing_actions, pt_slope_offset, pt_surface,                   &
     55               pt_vertical_gradient, sin_alpha_surface
     56
     57    USE grid_variables,                                                                            &
    5758        ONLY:  dx
    58        
    59     USE indices,                                                               &
     59
     60    USE indices,                                                                                   &
    6061        ONLY:  ngp_2dh, nx, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
    61        
     62
    6263    USE kinds
    6364
     
    7071    INTEGER(iwp) ::  j        !<
    7172    INTEGER(iwp) ::  k        !<
    72    
     73
    7374    REAL(wp)     ::  alpha    !<
    7475    REAL(wp)     ::  height   !<
    7576    REAL(wp)     ::  pt_value !<
    7677    REAL(wp)     ::  radius   !<
    77    
     78
    7879    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init_local !<
    7980
     
    8687
    8788!
    88 !--       Compute height of grid-point relative to lower left corner of
    89 !--       the total domain.
    90 !--       First compute the distance between the actual grid point and the
    91 !--       lower left corner as well as the angle between the line connecting
    92 !--       these points and the bottom of the model.
     89!--       Compute height of grid-point relative to lower left corner of the total domain.
     90!--       First compute the distance between the actual grid point and the lower left corner as well
     91!--       as the angle between the line connecting these points and the bottom of the model.
    9392          IF ( k /= nzb )  THEN
    9493             radius = SQRT( ( i * dx )**2 + zu(k)**2 )
     
    106105!--       Compute temperatures in the rotated coordinate system
    107106          alpha    = alpha + alpha_surface / 180.0_wp * pi
    108           pt_value = pt_surface + radius * SIN( alpha ) * &
    109                                   pt_vertical_gradient(1) / 100.0_wp
     107          pt_value = pt_surface + radius * SIN( alpha ) * pt_vertical_gradient(1) / 100.0_wp
    110108          pt_slope_ref(k,i) = pt_value
    111        ENDDO               
     109       ENDDO
    112110    ENDDO
    113111
    114112!
    115 !-- Temperature difference between left and right boundary of the total domain,
    116 !-- used for the cyclic boundary in x-direction
    117     pt_slope_offset = (nx+1) * dx * sin_alpha_surface * &
    118                       pt_vertical_gradient(1) / 100.0_wp
     113!-- Temperature difference between left and right boundary of the total domain, used for the cyclic
     114!-- boundary in x-direction
     115    pt_slope_offset = (nx+1) * dx * sin_alpha_surface * pt_vertical_gradient(1) / 100.0_wp
    119116
    120117
     
    129126
    130127!
    131 !--    Recompute the mean initial temperature profile (mean along x-direction of
    132 !--    the rotated coordinate system)
     128!--    Recompute the mean initial temperature profile (mean along x-direction of the rotated
     129!--    coordinate system)
    133130       ALLOCATE( pt_init_local(nzb:nzt+1) )
    134131       pt_init_local = 0.0_wp
     
    143140#if defined( __parallel )
    144141       IF ( collective_wait )  CALL MPI_BARRIER( comm2d, ierr )
    145        CALL MPI_ALLREDUCE( pt_init_local, pt_init, nzt+2-nzb, MPI_REAL, &
    146                             MPI_SUM, comm2d, ierr )
     142       CALL MPI_ALLREDUCE( pt_init_local, pt_init, nzt+2-nzb, MPI_REAL, MPI_SUM, comm2d, ierr )
    147143#else
    148144       pt_init = pt_init_local
Note: See TracChangeset for help on using the changeset viewer.