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

    r4481 r4648  
    11!> @file ocean_mod.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 2017-2020 Leibniz Universitaet Hannover
    18 !--------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    1918!
    2019! Current revisions:
    2120! -----------------
    22 ! 
    23 ! 
     21!
     22!
    2423! Former revisions:
    2524! -----------------
    2625! $Id$
    27 ! split from check_parameters as separate file to avoid circular dependency
    28 ! with ocean_mod
     26! file re-formatted to follow the PALM coding standard
    2927!
    30 !
     28! 4481 2020-03-31 18:55:54Z maronga
     29! split from check_parameters as separate file to avoid circular dependency with ocean_mod
     30!
     31!
    3132!
    3233!
     
    3839! ------------
    3940!> Inititalizes the vertical profiles of scalar quantities.
    40 !------------------------------------------------------------------------------!
    41  SUBROUTINE init_vertical_profiles( vertical_gradient_level_ind,               &
    42                                     vertical_gradient_level,                   &
    43                                     vertical_gradient, initial_profile,        &
     41!--------------------------------------------------------------------------------------------------!
     42 SUBROUTINE init_vertical_profiles( vertical_gradient_level_ind,                                   &
     43                                    vertical_gradient_level,                                       &
     44                                    vertical_gradient, initial_profile,                            &
    4445                                    surface_value, bc_top_gradient )
    4546
    46     USE arrays_3d,                                                             &
     47    USE arrays_3d,                                                                                 &
    4748        ONLY:  dzu, zu
    4849
    49     USE control_parameters,                                                    &
     50    USE control_parameters,                                                                        &
    5051        ONLY:  ocean_mode
    5152
    52     USE indices,                                                               &
     53    USE indices,                                                                                   &
    5354        ONLY:  nz, nzt
    5455
     
    5960    INTEGER(iwp) ::  i  !< loop counter
    6061    INTEGER(iwp) ::  k  !< loop counter
     62
    6163    INTEGER(iwp), DIMENSION(1:10) ::  vertical_gradient_level_ind  !< vertical grid indices for gradient levels
    6264
     
    7779       DO  k = 1, nzt+1
    7880          IF ( i < 11 )  THEN
    79              IF ( vertical_gradient_level(i) < zu(k)  .AND.            &
     81             IF ( vertical_gradient_level(i) < zu(k)  .AND.                                        &
    8082                  vertical_gradient_level(i) >= 0.0_wp )  THEN
    8183                gradient = vertical_gradient(i) / 100.0_wp
     
    103105
    104106!
    105 !--    In ocean mode, profiles are constructed starting from the ocean surface,
    106 !--    which is at the top of the model domain
     107!--    In ocean mode, profiles are constructed starting from the ocean surface, which is at the top
     108!--    of the model domain
    107109       vertical_gradient_level_ind(1) = nzt+1
    108110       DO  k = nzt, 0, -1
    109111          IF ( i < 11 )  THEN
    110              IF ( vertical_gradient_level(i) > zu(k)  .AND.            &
     112             IF ( vertical_gradient_level(i) > zu(k)  .AND.                                        &
    111113                  vertical_gradient_level(i) <= 0.0_wp )  THEN
    112114                gradient = vertical_gradient(i) / 100.0_wp
     
    119121                initial_profile(k) = initial_profile(k+1) - dzu(k+1) * gradient
    120122             ELSE
    121                 initial_profile(k)   = surface_value - 0.5_wp * dzu(k+1) *     &
    122                                                        gradient
    123                 initial_profile(k+1) = surface_value + 0.5_wp * dzu(k+1) *     &
    124                                                        gradient
     123                initial_profile(k)   = surface_value - 0.5_wp * dzu(k+1) * gradient
     124                initial_profile(k+1) = surface_value + 0.5_wp * dzu(k+1) * gradient
    125125             ENDIF
    126126          ELSE
     
    143143!
    144144!-- Store gradient at the top boundary for possible Neumann boundary condition
    145     bc_top_gradient  = ( initial_profile(nzt+1) - initial_profile(nzt) ) /     &
    146                        dzu(nzt+1)
     145    bc_top_gradient  = ( initial_profile(nzt+1) - initial_profile(nzt) ) / dzu(nzt+1)
    147146
    148147 END SUBROUTINE init_vertical_profiles
Note: See TracChangeset for help on using the changeset viewer.