Ignore:
Timestamp:
Apr 3, 2020 11:34:29 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/advec_u_pw.f90

    r4360 r4488  
    11!> @file advec_u_pw.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:
     
    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! variables documented
     
    3739! ------------
    3840!> Advection term for u velocity-component using Piacsek and Williams.
    39 !> Vertical advection at the first grid point above the surface is done with
    40 !> normal centred differences, because otherwise no information from the surface
    41 !> would be communicated upwards due to w=0 at K=nzb.
    42 !------------------------------------------------------------------------------!
     41!> Vertical advection at the first grid point above the surface is done with normal centred
     42!> differences, because otherwise no information from the surface would be communicated upwards due
     43!> to w=0 at K=nzb.
     44!--------------------------------------------------------------------------------------------------!
    4345 MODULE advec_u_pw_mod
    44  
     46
    4547
    4648    PRIVATE
     
    5153       MODULE PROCEDURE advec_u_pw_ij
    5254    END INTERFACE advec_u_pw
    53  
     55
    5456 CONTAINS
    5557
    5658
    57 !------------------------------------------------------------------------------!
     59!--------------------------------------------------------------------------------------------------!
    5860! Description:
    5961! ------------
    6062!> Call for all grid points
    61 !------------------------------------------------------------------------------!
    62     SUBROUTINE advec_u_pw
     63!--------------------------------------------------------------------------------------------------!
     64 SUBROUTINE advec_u_pw
    6365
    64        USE arrays_3d,                                                          &
    65            ONLY:  ddzw, tend, u, v, w
     66    USE arrays_3d,                                                                                 &
     67        ONLY:  ddzw, tend, u, v, w
    6668
    67        USE control_parameters,                                                 &
    68            ONLY:  u_gtrans, v_gtrans
     69    USE control_parameters,                                                                        &
     70        ONLY:  u_gtrans, v_gtrans
    6971
    70        USE grid_variables,                                                     &
    71            ONLY:  ddx, ddy
     72    USE grid_variables,                                                                            &
     73        ONLY:  ddx, ddy
    7274
    73        USE indices,                                                            &
    74            ONLY:  nxlu, nxr, nyn, nys, nzb, nzt
     75    USE indices,                                                                                   &
     76        ONLY:  nxlu, nxr, nyn, nys, nzb, nzt
    7577
    76        USE kinds
     78    USE kinds
    7779
    7880
    79        IMPLICIT NONE
     81    IMPLICIT NONE
    8082
    81        INTEGER(iwp) ::  i !< grid index along x-direction
    82        INTEGER(iwp) ::  j !< grid index along y-direction
    83        INTEGER(iwp) ::  k !< grid index along z-direction
    84        
    85        REAL(wp)    ::  gu !< Galilei-transformation velocity along x
    86        REAL(wp)    ::  gv !< Galilei-transformation velocity along y
    87  
    88        gu = 2.0_wp * u_gtrans
    89        gv = 2.0_wp * v_gtrans
    90        DO  i = nxlu, nxr
    91           DO  j = nys, nyn
    92              DO  k = nzb+1, nzt
    93                 tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                        &
    94                          ( u(k,j,i+1) * ( u(k,j,i+1) + u(k,j,i) - gu )         &
    95                          - u(k,j,i-1) * ( u(k,j,i) + u(k,j,i-1) - gu ) ) * ddx &
    96                        + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )     &
    97                          - u(k,j-1,i) * ( v(k,j,i) + v(k,j,i-1) - gv ) ) * ddy &
    98                        + ( u(k+1,j,i) * ( w(k,j,i) + w(k,j,i-1) )              &
    99                          - u(k-1,j,i) * ( w(k-1,j,i) + w(k-1,j,i-1) ) )        &
    100                                                                   * ddzw(k)    &
    101                                                       )
    102              ENDDO
     83    INTEGER(iwp) ::  i !< grid index along x-direction
     84    INTEGER(iwp) ::  j !< grid index along y-direction
     85    INTEGER(iwp) ::  k !< grid index along z-direction
     86
     87    REAL(wp)     ::  gu !< Galilei-transformation velocity along x
     88    REAL(wp)     ::  gv !< Galilei-transformation velocity along y
     89
     90    gu = 2.0_wp * u_gtrans
     91    gv = 2.0_wp * v_gtrans
     92    DO  i = nxlu, nxr
     93       DO  j = nys, nyn
     94          DO  k = nzb+1, nzt
     95             tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                                               &
     96                           ( u(k,j,i+1)   * ( u(k,j,i+1) + u(k,j,i) - gu )                         &
     97                           - u(k,j,i-1)   * ( u(k,j,i)   + u(k,j,i-1) - gu ) ) * ddx               &
     98                           + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )                     &
     99                           - u(k,j-1,i)   * ( v(k,j,i)   + v(k,j,i-1) - gv ) ) * ddy               &
     100                           + ( u(k+1,j,i) * ( w(k,j,i)   + w(k,j,i-1) )                            &
     101                           - u(k-1,j,i)   * ( w(k-1,j,i) + w(k-1,j,i-1) ) )    * ddzw(k)           &
     102                                                   )
    103103          ENDDO
    104104       ENDDO
     105    ENDDO
    105106
    106     END SUBROUTINE advec_u_pw
     107 END SUBROUTINE advec_u_pw
    107108
    108109
    109 !------------------------------------------------------------------------------!
     110!--------------------------------------------------------------------------------------------------!
    110111! Description:
    111112! ------------
    112113!> Call for grid point i,j
    113 !------------------------------------------------------------------------------!
    114     SUBROUTINE advec_u_pw_ij( i, j )
     114!--------------------------------------------------------------------------------------------------!
     115 SUBROUTINE advec_u_pw_ij( i, j )
    115116
    116        USE arrays_3d,                                                          &
    117            ONLY:  ddzw, tend, u, v, w
     117    USE arrays_3d,                                                                                 &
     118        ONLY:  ddzw, tend, u, v, w
    118119
    119        USE control_parameters,                                                 &
    120            ONLY:  u_gtrans, v_gtrans
     120    USE control_parameters,                                                                        &
     121        ONLY:  u_gtrans, v_gtrans
    121122
    122        USE grid_variables,                                                     &
    123            ONLY:  ddx, ddy
     123    USE grid_variables,                                                                            &
     124        ONLY:  ddx, ddy
    124125
    125        USE indices,                                                            &
    126            ONLY:  nzb, nzt
     126    USE indices,                                                                                   &
     127        ONLY:  nzb, nzt
    127128
    128        USE kinds
     129    USE kinds
    129130
    130131
    131        IMPLICIT NONE
     132    IMPLICIT NONE
    132133
    133        INTEGER(iwp) ::  i !< grid index along x-direction
    134        INTEGER(iwp) ::  j !< grid index along y-direction
    135        INTEGER(iwp) ::  k !< grid index along z-direction
    136        
    137        REAL(wp)    ::  gu !< Galilei-transformation velocity along x
    138        REAL(wp)    ::  gv !< Galilei-transformation velocity along y
     134    INTEGER(iwp) ::  i !< grid index along x-direction
     135    INTEGER(iwp) ::  j !< grid index along y-direction
     136    INTEGER(iwp) ::  k !< grid index along z-direction
    139137
    140        gu = 2.0_wp * u_gtrans
    141        gv = 2.0_wp * v_gtrans
    142        DO  k = nzb+1, nzt
    143           tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                              &
    144                          ( u(k,j,i+1) * ( u(k,j,i+1) + u(k,j,i) - gu )         &
    145                          - u(k,j,i-1) * ( u(k,j,i) + u(k,j,i-1) - gu ) ) * ddx &
    146                        + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )     &
    147                          - u(k,j-1,i) * ( v(k,j,i) + v(k,j,i-1) - gv ) ) * ddy &
    148                        + ( u(k+1,j,i) * ( w(k,j,i) + w(k,j,i-1) )              &
    149                          - u(k-1,j,i) * ( w(k-1,j,i) + w(k-1,j,i-1) ) )        &
    150                                                                   * ddzw(k)    &
    151                                                 )
    152        ENDDO
     138    REAL(wp)     ::  gu !< Galilei-transformation velocity along x
     139    REAL(wp)     ::  gv !< Galilei-transformation velocity along y
    153140
    154     END SUBROUTINE advec_u_pw_ij
     141    gu = 2.0_wp * u_gtrans
     142    gv = 2.0_wp * v_gtrans
     143    DO  k = nzb+1, nzt
     144       tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                                                     &
     145                     ( u(k,j,i+1)   * ( u(k,j,i+1) + u(k,j,i) - gu )                               &
     146                     - u(k,j,i-1)   * ( u(k,j,i)   + u(k,j,i-1) - gu ) ) * ddx                     &
     147                     + ( u(k,j+1,i) * ( v(k,j+1,i) + v(k,j+1,i-1) - gv )                           &
     148                     - u(k,j-1,i)   * ( v(k,j,i)   + v(k,j,i-1) - gv ) ) * ddy                     &
     149                     + ( u(k+1,j,i) * ( w(k,j,i)   + w(k,j,i-1) )                                  &
     150                     - u(k-1,j,i)   * ( w(k-1,j,i) + w(k-1,j,i-1) ) )    * ddzw(k)                 &
     151                                             )
     152    ENDDO
     153
     154 END SUBROUTINE advec_u_pw_ij
    155155
    156156 END MODULE advec_u_pw_mod
Note: See TracChangeset for help on using the changeset viewer.