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

    r4457 r4648  
    11!> @file init_rankine.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
    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
    3032! Corrected "Former revisions" section
    31 ! 
     33!
    3234! 3655 2019-01-07 16:51:22Z knoop
    3335! Modularization of all bulk cloud physics code components
     
    3941! Description:
    4042! ------------
    41 !> Initialize a (nondivergent) Rankine eddy with a vertical axis in order to test
    42 !> the advection terms and the pressure solver.
    43 !------------------------------------------------------------------------------!
     43!> Initialize a (nondivergent) Rankine eddy with a vertical axis in order to test the advection
     44!> terms and the pressure solver.
     45!--------------------------------------------------------------------------------------------------!
    4446 SUBROUTINE init_rankine
    45  
    46 
    47     USE arrays_3d,                                                             &
     47
     48
     49    USE arrays_3d,                                                                                 &
    4850        ONLY:  pt, pt_init, u, u_init, v, v_init
    4951
    50     USE control_parameters,                                                    &
    51         ONLY:  initializing_actions, n_sor, nsor, nsor_ini   
    52 
    53     USE basic_constants_and_equations_mod,                                     &
     52    USE control_parameters,                                                                        &
     53        ONLY:  initializing_actions, n_sor, nsor, nsor_ini
     54
     55    USE basic_constants_and_equations_mod,                                                         &
    5456        ONLY:  pi
    5557
    56     USE exchange_horiz_mod,                                                    &
     58    USE exchange_horiz_mod,                                                                        &
    5759        ONLY:  exchange_horiz
    5860
    59     USE grid_variables,                                                        &
    60         ONLY:  dx, dy 
    61 
    62     USE indices,                                                               &
    63         ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt     
    64                
     61    USE grid_variables,                                                                            &
     62        ONLY:  dx, dy
     63
     64    USE indices,                                                                                   &
     65        ONLY:  nbgp, nx, nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
     66
    6567    USE kinds
    6668
     
    7476    INTEGER(iwp) ::  kc1 !<
    7577    INTEGER(iwp) ::  kc2 !<
    76    
     78
    7779    REAL(wp)     ::  alpha  !<
    7880    REAL(wp)     ::  betrag !<
Note: See TracChangeset for help on using the changeset viewer.