Ignore:
Timestamp:
Nov 26, 2020 4:02:39 PM (3 years ago)
Author:
raasch
Message:

files re-formatted to follow the PALM coding standard

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/outflow_turbulence.f90

    r4360 r4797  
    11!> @file outflow_turbulence.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: outflow_turbulence.f90 3241 2018-09-12 15:02:00Z raasch $
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 3241 2018-09-12 15:02:00Z raasch
    2729! Corrected "Former revisions" section
    28 ! 
     30!
    2931! 3241 2018-09-12 15:02:00Z raasch
    3032! unused variables removed
     
    3234! 2050 2016-11-08 15:00:55Z gronemeier
    3335! Initial version
    34 ! 
     36!
    3537!
    3638! Description:
    3739! ------------
    38 !> Routine based on inflow_turbulence.f90. Copies values of 3d data from a 2d
    39 !> vertical source plane (defined by outflow_source_plane) to the outflow
    40 !> boundary.
    41 !------------------------------------------------------------------------------!
     40!> Routine based on inflow_turbulence.f90. Copies values of 3d data from a 2d vertical source plane
     41!> (defined by outflow_source_plane) to the outflow boundary.
     42!--------------------------------------------------------------------------------------------------!
    4243 SUBROUTINE outflow_turbulence
    4344
    44     USE arrays_3d,                                                             &
     45    USE arrays_3d,                                                                                 &
    4546        ONLY:  e, pt, q, s, u, v, w
    4647
    47     USE control_parameters,                                                    &
     48    USE control_parameters,                                                                        &
    4849        ONLY:  humidity, passive_scalar, outflow_source_plane
    4950
    50     USE cpulog,                                                                &
     51    USE cpulog,                                                                                    &
    5152        ONLY:  cpu_log, log_point
    5253
    53     USE grid_variables,                                                        &
     54    USE grid_variables,                                                                            &
    5455        ONLY:  ddx
    5556
    56     USE indices,                                                               &
     57    USE indices,                                                                                   &
    5758        ONLY:  nbgp, nx, nxr, nyn, nys, nyng, nysg, nzb, nzt
    5859
    5960    USE kinds
    6061
    61     USE pegrid!,                                                                &
     62    USE pegrid!,                                                                                    &
    6263        !ONLY:  comm1dx, id_outflow, id_outflow_source, ierr, myidx, status
    6364
     
    7071    INTEGER(iwp) ::  ngp_ofv  !< number of grid points stored in outflow_val
    7172
    72     REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::                         &
    73        outflow_val            !< values to be copied to the outflow boundary
     73    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,7,nbgp) ::  outflow_val  !< values to be copied to the outflow boundary
    7474
    7575
     
    9494                outflow_val(k,j,4,l) = pt(k,j,i)
    9595                outflow_val(k,j,5,l) = e(k,j,i)
    96                 IF ( humidity  )                                               &
     96                IF ( humidity  )                                                                   &
    9797                   outflow_val(k,j,6,l) = q(k,j,i)
    98                 IF ( passive_scalar )                                          &
     98                IF ( passive_scalar )                                                              &
    9999                   outflow_val(k,j,7,l) = s(k,j,i)
    100100
     
    115115             outflow_val(k,j,4,l) = pt(k,j,i)
    116116             outflow_val(k,j,5,l) = e(k,j,i)
    117              IF ( humidity  )                                                  &
     117             IF ( humidity  )                                                                      &
    118118                outflow_val(k,j,6,l) = q(k,j,i)
    119              IF ( passive_scalar )                                             &
     119             IF ( passive_scalar )                                                                 &
    120120                outflow_val(k,j,7,l) = s(k,j,i)
    121121
     
    131131    IF ( myidx == id_outflow_source  .AND.  myidx /= id_outflow )  THEN
    132132
    133        CALL MPI_SEND( outflow_val(nzb,nysg,1,1), ngp_ofv, MPI_REAL,            &
    134                       id_outflow, 1, comm1dx, ierr )
     133       CALL MPI_SEND( outflow_val(nzb,nysg,1,1), ngp_ofv, MPI_REAL, id_outflow, 1, comm1dx, ierr )
    135134
    136135    ELSEIF ( myidx /= id_outflow_source  .AND.  myidx == id_outflow )  THEN
    137136
    138137       outflow_val = 0.0_wp
    139        CALL MPI_RECV( outflow_val(nzb,nysg,1,1), ngp_ofv, MPI_REAL,           &
    140                       id_outflow_source, 1, comm1dx, status, ierr )
     138       CALL MPI_RECV( outflow_val(nzb,nysg,1,1), ngp_ofv, MPI_REAL, id_outflow_source, 1, comm1dx, &
     139                      status, ierr )
    141140
    142141    ENDIF
     
    157156             e(k,j,nx+1:nx+nbgp)  = MAX( e(k,j,nx+1:nx+nbgp), 0.0_wp )
    158157
    159              IF ( humidity )                                                   &
     158             IF ( humidity )                                                                       &
    160159                q(k,j,nx+1:nx+nbgp)  = outflow_val(k,j,6,1:nbgp)
    161              IF ( passive_scalar )                                             &
     160             IF ( passive_scalar )                                                                 &
    162161                s(k,j,nx+1:nx+nbgp)  = outflow_val(k,j,7,1:nbgp)
    163162
Note: See TracChangeset for help on using the changeset viewer.