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

    r4360 r4488  
    11!> @file advec_s_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! 3927 2019-04-23 13:24:29Z raasch
    3032! pointer attribute removed from scalar 3d-array for performance reasons
    31 ! 
     33!
    3234! 3665 2019-01-10 08:28:24Z raasch
    3335! unused variables removed
    34 ! 
     36!
    3537! 3655 2019-01-07 16:51:22Z knoop
    3638! nopointer option removed
     
    4244! Description:
    4345! ------------
    44 !> Advection term for scalar variables using the Piacsek and Williams scheme
    45 !> (form C3). Contrary to PW itself, for reasons of accuracy their scheme is
    46 !> slightly modified as follows: the values of those scalars that are used for
    47 !> the computation of the flux divergence are reduced by the value of the
    48 !> relevant scalar at the location where the difference is computed (sk(k,j,i)).
     46!> Advection term for scalar variables using the Piacsek and Williams scheme (form C3). Contrary to
     47!> PW itself, for reasons of accuracy their scheme is slightly modified as follows: the values of
     48!> those scalars that are used for the computation of the flux divergence are reduced by the value
     49!> of the relevant scalar at the location where the difference is computed (sk(k,j,i)).
    4950!> NOTE: at the first grid point above the surface computation still takes place!
    50 !------------------------------------------------------------------------------!
     51!--------------------------------------------------------------------------------------------------!
    5152 MODULE advec_s_pw_mod
    52  
     53
    5354
    5455    PRIVATE
     
    5960       MODULE PROCEDURE advec_s_pw_ij
    6061    END INTERFACE
    61  
     62
    6263 CONTAINS
    6364
    6465
    65 !------------------------------------------------------------------------------!
     66!--------------------------------------------------------------------------------------------------!
    6667! Description:
    6768! ------------
    6869!> Call for all grid points
    69 !------------------------------------------------------------------------------!
    70     SUBROUTINE advec_s_pw( sk )
     70!--------------------------------------------------------------------------------------------------!
     71 SUBROUTINE advec_s_pw( sk )
    7172
    72        USE arrays_3d,                                                          &
    73            ONLY:  dd2zu, tend, u, u_stokes_zu, v, v_stokes_zu, w
     73    USE arrays_3d,                                                                                 &
     74        ONLY:  dd2zu, tend, u, u_stokes_zu, v, v_stokes_zu, w
    7475
    75        USE control_parameters,                                                 &
    76            ONLY:  u_gtrans, v_gtrans
     76    USE control_parameters,                                                                        &
     77        ONLY:  u_gtrans, v_gtrans
    7778
    78        USE grid_variables,                                                     &
    79            ONLY:  ddx, ddy
     79    USE grid_variables,                                                                            &
     80        ONLY:  ddx, ddy
    8081
    81        USE indices,                                                            &
    82            ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
     82    USE indices,                                                                                   &
     83        ONLY:  nxl, nxlg, nxr, nxrg, nyn, nyng, nys, nysg, nzb, nzt
    8384
    84        USE kinds
     85    USE kinds
    8586
    8687
    87        IMPLICIT NONE
     88    IMPLICIT NONE
    8889
    89        INTEGER(iwp) ::  i !< grid index along x-direction
    90        INTEGER(iwp) ::  j !< grid index along y-direction
    91        INTEGER(iwp) ::  k !< grid index along z-direction
     90    INTEGER(iwp) ::  i !< grid index along x-direction
     91    INTEGER(iwp) ::  j !< grid index along y-direction
     92    INTEGER(iwp) ::  k !< grid index along z-direction
    9293
    93        REAL(wp)     ::  gu  !< local additional advective velocity
    94        REAL(wp)     ::  gv  !< local additional advective velocity
     94    REAL(wp)     ::  gu  !< local additional advective velocity
     95    REAL(wp)     ::  gv  !< local additional advective velocity
    9596
    96        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
    97  
     97    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
    9898
    99        DO  i = nxl, nxr
    100           DO  j = nys, nyn
    101              DO  k = nzb+1, nzt
     99
     100    DO  i = nxl, nxr
     101       DO  j = nys, nyn
     102          DO  k = nzb+1, nzt
    102103
    103104!
    104 !--             Galilean transformation + Stokes drift velocity (ocean only)
    105                 gu = u_gtrans - u_stokes_zu(k)
    106                 gv = v_gtrans - v_stokes_zu(k)
     105!--          Galilean transformation + Stokes drift velocity (ocean only)
     106             gu = u_gtrans - u_stokes_zu(k)
     107             gv = v_gtrans - v_stokes_zu(k)
    107108
    108                 tend(k,j,i) = tend(k,j,i) +                                    &
    109                                      ( -0.5_wp * ( ( u(k,j,i+1) - gu       ) * &
    110                                                    ( sk(k,j,i+1) - sk(k,j,i) ) &
    111                                                  - ( u(k,j,i)   - gu       ) * &
    112                                                    ( sk(k,j,i-1) - sk(k,j,i) ) &
    113                                                  ) * ddx                       &
    114                                        -0.5_wp * ( ( v(k,j+1,i) - gv       ) * &
    115                                                    ( sk(k,j+1,i) - sk(k,j,i) ) &
    116                                                  - ( v(k,j,i)   - gv       ) * &
    117                                                    ( sk(k,j-1,i) - sk(k,j,i) ) &
    118                                                  ) * ddy                       &
    119                                        -         (   w(k,j,i)                * &
    120                                                    ( sk(k+1,j,i) - sk(k,j,i) ) &
    121                                                  -   w(k-1,j,i)              * &
    122                                                    ( sk(k-1,j,i) - sk(k,j,i) ) &
    123                                                  ) * dd2zu(k)                  &
    124                                       )
    125              ENDDO
     109             tend(k,j,i) = tend(k,j,i) +                                                           &
     110                                  ( -0.5_wp * ( ( u(k,j,i+1)  - gu        ) *                      &
     111                                                ( sk(k,j,i+1) - sk(k,j,i) )                        &
     112                                              - ( u(k,j,i)    - gu        ) *                      &
     113                                                ( sk(k,j,i-1) - sk(k,j,i) )                        &
     114                                              ) * ddx                                              &
     115                                    -0.5_wp * ( ( v(k,j+1,i)  - gv        ) *                      &
     116                                                ( sk(k,j+1,i) - sk(k,j,i) )                        &
     117                                              - ( v(k,j,i)    - gv        ) *                      &
     118                                                ( sk(k,j-1,i) - sk(k,j,i) )                        &
     119                                              ) * ddy                                              &
     120                                    -         (   w(k,j,i)                  *                      &
     121                                                ( sk(k+1,j,i) - sk(k,j,i) )                        &
     122                                              -   w(k-1,j,i)                *                      &
     123                                                ( sk(k-1,j,i) - sk(k,j,i) )                        &
     124                                              ) * dd2zu(k)                                         &
     125                                   )
    126126          ENDDO
    127127       ENDDO
     128    ENDDO
    128129
    129     END SUBROUTINE advec_s_pw
     130 END SUBROUTINE advec_s_pw
    130131
    131132
    132 !------------------------------------------------------------------------------!
     133!--------------------------------------------------------------------------------------------------!
    133134! Description:
    134135! ------------
    135136!> Call for grid point i,j
    136 !------------------------------------------------------------------------------!
    137     SUBROUTINE advec_s_pw_ij( i, j, sk )
     137!--------------------------------------------------------------------------------------------------!
     138 SUBROUTINE advec_s_pw_ij( i, j, sk )
    138139
    139        USE arrays_3d,                                                          &
    140            ONLY:  dd2zu, tend, u, u_stokes_zu, v, v_stokes_zu, w
     140    USE arrays_3d,                                                                                 &
     141        ONLY:  dd2zu, tend, u, u_stokes_zu, v, v_stokes_zu, w
    141142
    142        USE control_parameters,                                                 &
    143            ONLY:  u_gtrans, v_gtrans
     143    USE control_parameters,                                                                        &
     144        ONLY:  u_gtrans, v_gtrans
    144145
    145        USE grid_variables,                                                     &
    146            ONLY:  ddx, ddy
     146    USE grid_variables,                                                                            &
     147        ONLY:  ddx, ddy
    147148
    148        USE indices,                                                            &
    149            ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzt
     149    USE indices,                                                                                   &
     150        ONLY:  nxlg, nxrg, nyng, nysg, nzb, nzt
    150151
    151        USE kinds
     152    USE kinds
    152153
    153154
    154        IMPLICIT NONE
     155    IMPLICIT NONE
    155156
    156        INTEGER(iwp) ::  i !< grid index along x-direction
    157        INTEGER(iwp) ::  j !< grid index along y-direction
    158        INTEGER(iwp) ::  k !< grid index along z-direction
     157    INTEGER(iwp) ::  i !< grid index along x-direction
     158    INTEGER(iwp) ::  j !< grid index along y-direction
     159    INTEGER(iwp) ::  k !< grid index along z-direction
    159160
    160        REAL(wp)     ::  gu  !< local additional advective velocity
    161        REAL(wp)     ::  gv  !< local additional advective velocity
     161    REAL(wp)     ::  gu  !< local additional advective velocity
     162    REAL(wp)     ::  gv  !< local additional advective velocity
    162163
    163        REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
     164    REAL(wp), DIMENSION(nzb:nzt+1,nysg:nyng,nxlg:nxrg) ::  sk
    164165
    165166
    166        DO  k = nzb+1, nzt
     167    DO  k = nzb+1, nzt
    167168
    168169!
    169 !--       Galilean transformation + Stokes drift velocity (ocean only)
    170           gu = u_gtrans - u_stokes_zu(k)
    171           gv = v_gtrans - v_stokes_zu(k)
     170!--    Galilean transformation + Stokes drift velocity (ocean only)
     171       gu = u_gtrans - u_stokes_zu(k)
     172       gv = v_gtrans - v_stokes_zu(k)
    172173
    173           tend(k,j,i) = tend(k,j,i) +                                          &
    174                                     ( -0.5_wp * ( ( u(k,j,i+1) - gu        ) * &
    175                                                   ( sk(k,j,i+1) - sk(k,j,i) )  &
    176                                                 - ( u(k,j,i)   - gu        ) * &
    177                                                   ( sk(k,j,i-1) - sk(k,j,i) )  &
    178                                                 ) * ddx                        &
    179                                       -0.5_wp * ( ( v(k,j+1,i) - gv       ) *  &
    180                                                   ( sk(k,j+1,i) - sk(k,j,i) )  &
    181                                                 - ( v(k,j,i)   - gv       ) *  &
    182                                                   ( sk(k,j-1,i) - sk(k,j,i) )  &
    183                                                 ) * ddy                        &
    184                                       -         (   w(k,j,i)                *  &
    185                                                   ( sk(k+1,j,i) - sk(k,j,i) )  &
    186                                                 -   w(k-1,j,i)              *  &
    187                                                   ( sk(k-1,j,i) - sk(k,j,i) )  &
    188                                                 ) * dd2zu(k)                   &
    189                                     )
    190        ENDDO
     174       tend(k,j,i) = tend(k,j,i) +                                                                 &
     175                                 ( -0.5_wp * ( ( u(k,j,i+1)  - gu        ) *                      &
     176                                               ( sk(k,j,i+1) - sk(k,j,i) )                         &
     177                                             - ( u(k,j,i)    - gu        ) *                      &
     178                                               ( sk(k,j,i-1) - sk(k,j,i) )                         &
     179                                             ) * ddx                                               &
     180                                   -0.5_wp * ( ( v(k,j+1,i)  - gv        ) *                       &
     181                                               ( sk(k,j+1,i) - sk(k,j,i) )                         &
     182                                             - ( v(k,j,i)    - gv        ) *                       &
     183                                               ( sk(k,j-1,i) - sk(k,j,i) )                         &
     184                                             ) * ddy                                               &
     185                                   -         (   w(k,j,i)                  *                       &
     186                                               ( sk(k+1,j,i) - sk(k,j,i) )                         &
     187                                             -   w(k-1,j,i)                *                       &
     188                                               ( sk(k-1,j,i) - sk(k,j,i) )                         &
     189                                             ) * dd2zu(k)                                          &
     190                                 )
     191    ENDDO
    191192
    192     END SUBROUTINE advec_s_pw_ij
     193 END SUBROUTINE advec_s_pw_ij
    193194
    194195 END MODULE advec_s_pw_mod
Note: See TracChangeset for help on using the changeset viewer.