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_pt_anomaly.f90

    r4457 r4648  
    11!> @file init_pt_anomaly.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! 4457 2020-03-11 14:20:43Z raasch
    2729! use statement for exchange horiz added
    28 ! 
     30!
    2931! 4360 2020-01-07 11:25:50Z suehring
    30 ! Introduction of wall_flags_total_0, which currently sets bits based on static
    31 ! topography information used in wall_flags_static_0
    32 ! 
     32! Introduction of wall_flags_total_0, which currently sets bits based on static topography
     33! information used in wall_flags_static_0
     34!
    3335! 4329 2019-12-10 15:46:36Z motisi
    3436! Renamed wall_flags_0 to wall_flags_static_0
    35 ! 
     37!
    3638! 4182 2019-08-22 15:20:23Z scharf
    3739! Corrected "Former revisions" section
    38 ! 
     40!
    3941! 3655 2019-01-07 16:51:22Z knoop
    4042! Added topography flags
     
    4749! ------------
    4850!> Impose a temperature perturbation for an advection test.
    49 !------------------------------------------------------------------------------!
     51!--------------------------------------------------------------------------------------------------!
    5052 SUBROUTINE init_pt_anomaly
    5153
    5254
    53     USE arrays_3d,                                                             &
     55    USE arrays_3d,                                                                                 &
    5456        ONLY:  pt, zu
    5557
    5658    USE control_parameters
    5759
    58     USE exchange_horiz_mod,                                                    &
     60    USE exchange_horiz_mod,                                                                        &
    5961        ONLY:  exchange_horiz
    6062
    61     USE grid_variables,                                                        &
     63    USE grid_variables,                                                                            &
    6264        ONLY:  dx, dy
    6365
    64     USE indices,                                                               &
     66    USE indices,                                                                                   &
    6567        ONLY:  nbgp, nx, nxl, nxr, ny, nyn, nys, nzb, nzt, wall_flags_total_0
    6668
     
    7072
    7173    INTEGER(iwp) ::  i  !< grid index along x
    72     INTEGER(iwp) ::  ic !< center index along x 
     74    INTEGER(iwp) ::  ic !< center index along x
    7375    INTEGER(iwp) ::  j  !< grid index along y
    7476    INTEGER(iwp) ::  jc !< center index along y
     
    125127
    126128!
    127 !-- Initialize warm air bubble close to surface and homogenous elegonated
    128 !-- along x-Axis
     129!-- Initialize warm air bubble close to surface and homogenous elegonated along x-Axis
    129130    ELSEIF ( INDEX( initializing_actions, 'initialize_bubble' ) /= 0 )  THEN
    130131!
     
    141142                flag = MERGE( 1.0_wp, 0.0_wp, BTEST( wall_flags_total_0(k,j,i), 0 ) )
    142143
    143                 pt(k,j,i) = pt(k,j,i) +                                        &
    144                                EXP( -0.5 * ( (j* dy  - bubble_center_y) /      &
    145                                                        bubble_sigma_y )**2) *  &
    146                                EXP( -0.5 * ( (zu(k)  - bubble_center_z) /      &
    147                                                        bubble_sigma_z)**2) *   &
     144                pt(k,j,i) = pt(k,j,i) +                                                            &
     145                               EXP( -0.5 * ( (j* dy - bubble_center_y) / bubble_sigma_y )**2) *    &
     146                               EXP( -0.5 * ( (zu(k) - bubble_center_z) / bubble_sigma_z)**2)  *    &
    148147                               initial_temperature_difference * flag
    149148             ENDDO
Note: See TracChangeset for help on using the changeset viewer.