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

    r4360 r4488  
    11!> @file advec_v_pw.f90
    2 !------------------------------------------------------------------------------!
    3 !------------------------------------------------------------------------------!
     2!--------------------------------------------------------------------------------------------------!
    43! This file is part of the PALM model system.
    54!
    6 ! PALM is free software: you can redistribute it and/or modify it under the
    7 ! terms of the GNU General Public License as published by the Free Software
    8 ! Foundation, either version 3 of the License, or (at your option) any later
    9 ! 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.
    108!
    11 ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY
    12 ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR
    13 ! 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.
    1412!
    15 ! You should have received a copy of the GNU General Public License along with
    16 ! 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/>.
    1715!
    1816! Copyright 1997-2020 Leibniz Universitaet Hannover
    19 !------------------------------------------------------------------------------!
     17!--------------------------------------------------------------------------------------------------!
    2018!
    2119! Current revisions:
     
    2624! -----------------
    2725! $Id$
     26! file re-formatted to follow the PALM coding standard
     27!
     28! 4360 2020-01-07 11:25:50Z suehring
    2829! Corrected "Former revisions" section
    2930!
     
    3839! ------------
    3940!> Advection term for v velocity-component using Piacsek and Williams.
    40 !> Vertical advection at the first grid point above the surface is done with
    41 !> normal centred differences, because otherwise no information from the surface
    42 !> would be communicated upwards due to w=0 at K=nzb.
    43 !------------------------------------------------------------------------------!
     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!--------------------------------------------------------------------------------------------------!
    4445 MODULE advec_v_pw_mod
    4546 
     
    5657
    5758
    58 !------------------------------------------------------------------------------!
     59!--------------------------------------------------------------------------------------------------!
    5960! Description:
    6061! ------------
    6162!> Call for all grid points
    62 !------------------------------------------------------------------------------!
    63     SUBROUTINE advec_v_pw
     63!--------------------------------------------------------------------------------------------------!
     64 SUBROUTINE advec_v_pw
    6465
    65        USE arrays_3d,                                                          &
    66            ONLY:  ddzw, tend, u, v, w
     66    USE arrays_3d,                                                                                 &
     67        ONLY:  ddzw, tend, u, v, w
    6768
    68        USE control_parameters,                                                 &
    69            ONLY:  u_gtrans, v_gtrans
     69    USE control_parameters,                                                                        &
     70        ONLY:  u_gtrans, v_gtrans
    7071
    71        USE grid_variables,                                                     &
    72            ONLY:  ddx, ddy
     72    USE grid_variables,                                                                            &
     73        ONLY:  ddx, ddy
    7374
    74        USE indices,                                                            &
    75            ONLY:  nxl, nxr, nyn, nysv, nzb, nzt
     75    USE indices,                                                                                   &
     76        ONLY:  nxl, nxr, nyn, nysv, nzb, nzt
    7677
    77        USE kinds
     78    USE kinds
    7879
    7980
    80        IMPLICIT NONE
     81    IMPLICIT NONE
    8182
    82        INTEGER(iwp) ::  i !< grid index along x-direction
    83        INTEGER(iwp) ::  j !< grid index along y-direction
    84        INTEGER(iwp) ::  k !< grid index along z-direction
    85        
    86        REAL(wp)    ::  gu !< Galilei-transformation velocity along x
    87        REAL(wp)    ::  gv !< Galilei-transformation velocity along y
    88  
     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
    8989
    90        gu = 2.0_wp * u_gtrans
    91        gv = 2.0_wp * v_gtrans
    92        DO  i = nxl, nxr
    93           DO  j = nysv, nyn
    94              DO  k = nzb+1, nzt
    95                 tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                        &
    96                          ( v(k,j,i+1) * ( u(k,j-1,i+1) + u(k,j,i+1) - gu )     &
    97                          - v(k,j,i-1) * ( u(k,j-1,i) + u(k,j,i) - gu ) ) * ddx &
    98                        + ( v(k,j+1,i) * ( v(k,j+1,i) + v(k,j,i) - gv )         &
    99                          - v(k,j-1,i) * ( v(k,j,i) + v(k,j-1,i) - gv ) ) * ddy &
    100                        + ( v(k+1,j,i) * ( w(k,j-1,i) + w(k,j,i) )              &
    101                          - v(k-1,j,i) * ( w(k-1,j-1,i) + w(k-1,j,i) ) )        &
    102                                                                   * ddzw(k)    &
    103                                                       )
    104              ENDDO
     90
     91    gu = 2.0_wp * u_gtrans
     92    gv = 2.0_wp * v_gtrans
     93    DO  i = nxl, nxr
     94       DO  j = nysv, nyn
     95          DO  k = nzb+1, nzt
     96             tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                                               &
     97                           ( v(k,j,i+1)   * ( u(k,j-1,i+1) + u(k,j,i+1) - gu )                     &
     98                           - v(k,j,i-1)   * ( u(k,j-1,i)   + u(k,j,i)   - gu ) ) * ddx             &
     99                           + ( v(k,j+1,i) * ( v(k,j+1,i)   + v(k,j,i)   - gv )                     &
     100                           - v(k,j-1,i)   * ( v(k,j,i)     + v(k,j-1,i) - gv ) ) * ddy             &
     101                           + ( v(k+1,j,i) * ( w(k,j-1,i)   + w(k,j,i) )                            &
     102                           - v(k-1,j,i)   * ( w(k-1,j-1,i) + w(k-1,j,i) ) )      * ddzw(k)         &
     103                                                   )
    105104          ENDDO
    106105       ENDDO
     106    ENDDO
    107107
    108     END SUBROUTINE advec_v_pw
     108 END SUBROUTINE advec_v_pw
    109109
    110110
    111 !------------------------------------------------------------------------------!
     111!--------------------------------------------------------------------------------------------------!
    112112! Description:
    113113! ------------
    114114!> Call for grid point i,j
    115 !------------------------------------------------------------------------------!
    116     SUBROUTINE advec_v_pw_ij( i, j )
     115!--------------------------------------------------------------------------------------------------!
     116 SUBROUTINE advec_v_pw_ij( i, j )
    117117
    118        USE arrays_3d,                                                          &
    119            ONLY:  ddzw, tend, u, v, w
     118    USE arrays_3d,                                                                                 &
     119        ONLY:  ddzw, tend, u, v, w
    120120
    121        USE control_parameters,                                                 &
    122            ONLY:  u_gtrans, v_gtrans
     121    USE control_parameters,                                                                        &
     122        ONLY:  u_gtrans, v_gtrans
    123123
    124        USE grid_variables,                                                     &
    125            ONLY:  ddx, ddy
     124    USE grid_variables,                                                                            &
     125        ONLY:  ddx, ddy
    126126
    127        USE indices,                                                            &
    128            ONLY:  nzb, nzt
     127    USE indices,                                                                                   &
     128        ONLY:  nzb, nzt
    129129
    130        USE kinds
     130    USE kinds
    131131
    132132
    133        IMPLICIT NONE
     133    IMPLICIT NONE
    134134
    135        INTEGER(iwp) ::  i !< grid index along x-direction
    136        INTEGER(iwp) ::  j !< grid index along y-direction
    137        INTEGER(iwp) ::  k !< grid index along z-direction
    138        
    139        REAL(wp)    ::  gu !< Galilei-transformation velocity along x
    140        REAL(wp)    ::  gv !< Galilei-transformation velocity along y
     135    INTEGER(iwp) ::  i !< grid index along x-direction
     136    INTEGER(iwp) ::  j !< grid index along y-direction
     137    INTEGER(iwp) ::  k !< grid index along z-direction
     138   
     139    REAL(wp)     ::  gu !< Galilei-transformation velocity along x
     140    REAL(wp)     ::  gv !< Galilei-transformation velocity along y
    141141
    142142
    143        gu = 2.0_wp * u_gtrans
    144        gv = 2.0_wp * v_gtrans
    145        DO  k = nzb+1, nzt
    146           tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                              &
    147                          ( v(k,j,i+1) * ( u(k,j-1,i+1) + u(k,j,i+1) - gu )     &
    148                          - v(k,j,i-1) * ( u(k,j-1,i) + u(k,j,i) - gu ) ) * ddx &
    149                        + ( v(k,j+1,i) * ( v(k,j+1,i) + v(k,j,i) - gv )         &
    150                          - v(k,j-1,i) * ( v(k,j,i) + v(k,j-1,i) - gv ) ) * ddy &
    151                        + ( v(k+1,j,i) * ( w(k,j-1,i) + w(k,j,i) )              &
    152                          - v(k-1,j,i) * ( w(k-1,j-1,i) + w(k-1,j,i) ) )        &
    153                                                                   * ddzw(k)    &
    154                                                 )
    155        ENDDO
    156  
    157     END SUBROUTINE advec_v_pw_ij
     143    gu = 2.0_wp * u_gtrans
     144    gv = 2.0_wp * v_gtrans
     145    DO  k = nzb+1, nzt
     146       tend(k,j,i) = tend(k,j,i) - 0.25_wp * (                                                     &
     147                      ( v(k,j,i+1)   * ( u(k,j-1,i+1) + u(k,j,i+1) - gu )                          &
     148                      - v(k,j,i-1)   * ( u(k,j-1,i)   + u(k,j,i)   - gu ) ) * ddx                  &
     149                      + ( v(k,j+1,i) * ( v(k,j+1,i)   + v(k,j,i)   - gv )                          &
     150                      - v(k,j-1,i)   * ( v(k,j,i)     + v(k,j-1,i) - gv ) ) * ddy                  &
     151                      + ( v(k+1,j,i) * ( w(k,j-1,i)   + w(k,j,i) )                                 &
     152                      - v(k-1,j,i)   * ( w(k-1,j-1,i) + w(k-1,j,i) ) )      * ddzw(k)              &
     153                                             )
     154    ENDDO
     155
     156 END SUBROUTINE advec_v_pw_ij
    158157
    159158 END MODULE advec_v_pw_mod
Note: See TracChangeset for help on using the changeset viewer.