Ignore:
Timestamp:
Oct 7, 2015 11:56:08 PM (9 years ago)
Author:
knoop
Message:

Code annotations made doxygen readable

File:
1 edited

Legend:

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

    r1659 r1682  
    1 #if ! defined( __openacc )
    2  SUBROUTINE flow_statistics
    3 
     1!> @file flow_statistics.f90
    42!--------------------------------------------------------------------------------!
    53! This file is part of PALM.
     
    2119! Current revisions:
    2220! -----------------
    23 !
     21! Code annotations made doxygen readable
    2422!
    2523! Former revisions:
     
    146144! Description:
    147145! ------------
    148 ! Compute average profiles and further average flow quantities for the different
    149 ! user-defined (sub-)regions. The region indexed 0 is the total model domain.
    150 !
    151 ! NOTE: For simplicity, nzb_s_inner and nzb_diff_s_inner are being used as a
    152 ! ----  lower vertical index for k-loops for all variables, although strictly
    153 ! speaking the k-loops would have to be split up according to the staggered
    154 ! grid. However, this implies no error since staggered velocity components are
    155 ! zero at the walls and inside buildings.
     146!> Compute average profiles and further average flow quantities for the different
     147!> user-defined (sub-)regions. The region indexed 0 is the total model domain.
     148!>
     149!> @note For simplicity, nzb_s_inner and nzb_diff_s_inner are being used as a
     150!>       lower vertical index for k-loops for all variables, although strictly
     151!>      speaking the k-loops would have to be split up according to the staggered
     152!>       grid. However, this implies no error since staggered velocity components
     153!>       are zero at the walls and inside buildings.
    156154!------------------------------------------------------------------------------!
     155#if ! defined( __openacc )
     156 SUBROUTINE flow_statistics
     157 
    157158
    158159    USE arrays_3d,                                                             &
     
    206207    IMPLICIT NONE
    207208
    208     INTEGER(iwp) ::  i                   !:
    209     INTEGER(iwp) ::  j                   !:
    210     INTEGER(iwp) ::  k                   !:
    211     INTEGER(iwp) ::  nt                  !:
    212     INTEGER(iwp) ::  omp_get_thread_num  !:
    213     INTEGER(iwp) ::  sr                  !:
    214     INTEGER(iwp) ::  tn                  !:
     209    INTEGER(iwp) ::  i                   !<
     210    INTEGER(iwp) ::  j                   !<
     211    INTEGER(iwp) ::  k                   !<
     212    INTEGER(iwp) ::  nt                  !<
     213    INTEGER(iwp) ::  omp_get_thread_num  !<
     214    INTEGER(iwp) ::  sr                  !<
     215    INTEGER(iwp) ::  tn                  !<
    215216   
    216     LOGICAL ::  first  !:
     217    LOGICAL ::  first  !<
    217218   
    218     REAL(wp) ::  dptdz_threshold  !:
    219     REAL(wp) ::  fac              !:
    220     REAL(wp) ::  height           !:
    221     REAL(wp) ::  pts              !:
    222     REAL(wp) ::  sums_l_eper      !:
    223     REAL(wp) ::  sums_l_etot      !:
    224     REAL(wp) ::  ust              !:
    225     REAL(wp) ::  ust2             !:
    226     REAL(wp) ::  u2               !:
    227     REAL(wp) ::  vst              !:
    228     REAL(wp) ::  vst2             !:
    229     REAL(wp) ::  v2               !:
    230     REAL(wp) ::  w2               !:
    231     REAL(wp) ::  z_i(2)           !:
     219    REAL(wp) ::  dptdz_threshold  !<
     220    REAL(wp) ::  fac              !<
     221    REAL(wp) ::  height           !<
     222    REAL(wp) ::  pts              !<
     223    REAL(wp) ::  sums_l_eper      !<
     224    REAL(wp) ::  sums_l_etot      !<
     225    REAL(wp) ::  ust              !<
     226    REAL(wp) ::  ust2             !<
     227    REAL(wp) ::  u2               !<
     228    REAL(wp) ::  vst              !<
     229    REAL(wp) ::  vst2             !<
     230    REAL(wp) ::  v2               !<
     231    REAL(wp) ::  w2               !<
     232    REAL(wp) ::  z_i(2)           !<
    232233   
    233     REAL(wp) ::  dptdz(nzb+1:nzt+1)    !:
    234     REAL(wp) ::  sums_ll(nzb:nzt+1,2)  !:
     234    REAL(wp) ::  dptdz(nzb+1:nzt+1)    !<
     235    REAL(wp) ::  sums_ll(nzb:nzt+1,2)  !<
    235236
    236237    CALL cpu_log( log_point(10), 'flow_statistics', 'start' )
     
    15881589
    15891590!------------------------------------------------------------------------------!
    1590 ! flow statistics - accelerator version
     1591! Description:
     1592! ------------
     1593!> flow statistics - accelerator version
    15911594!------------------------------------------------------------------------------!
    15921595 SUBROUTINE flow_statistics
     
    16431646    IMPLICIT NONE
    16441647
    1645     INTEGER(iwp) ::  i                   !:
    1646     INTEGER(iwp) ::  j                   !:
    1647     INTEGER(iwp) ::  k                   !:
    1648     INTEGER(iwp) ::  nt                  !:
    1649     INTEGER(iwp) ::  omp_get_thread_num  !:
    1650     INTEGER(iwp) ::  sr                  !:
    1651     INTEGER(iwp) ::  tn                  !:
     1648    INTEGER(iwp) ::  i                   !<
     1649    INTEGER(iwp) ::  j                   !<
     1650    INTEGER(iwp) ::  k                   !<
     1651    INTEGER(iwp) ::  nt                  !<
     1652    INTEGER(iwp) ::  omp_get_thread_num  !<
     1653    INTEGER(iwp) ::  sr                  !<
     1654    INTEGER(iwp) ::  tn                  !<
    16521655   
    1653     LOGICAL ::  first  !:
     1656    LOGICAL ::  first  !<
    16541657   
    1655     REAL(wp) ::  dptdz_threshold  !:
    1656     REAL(wp) ::  fac              !:
    1657     REAL(wp) ::  height           !:
    1658     REAL(wp) ::  pts              !:
    1659     REAL(wp) ::  sums_l_eper      !:
    1660     REAL(wp) ::  sums_l_etot      !:
    1661     REAL(wp) ::  s1               !:
    1662     REAL(wp) ::  s2               !:
    1663     REAL(wp) ::  s3               !:
    1664     REAL(wp) ::  s4               !:
    1665     REAL(wp) ::  s5               !:
    1666     REAL(wp) ::  s6               !:
    1667     REAL(wp) ::  s7               !:
    1668     REAL(wp) ::  ust              !:
    1669     REAL(wp) ::  ust2             !:
    1670     REAL(wp) ::  u2               !:
    1671     REAL(wp) ::  vst              !:
    1672     REAL(wp) ::  vst2             !:
    1673     REAL(wp) ::  v2               !:
    1674     REAL(wp) ::  w2               !:
    1675     REAL(wp) ::  z_i(2)           !:
    1676 
    1677     REAL(wp) ::  dptdz(nzb+1:nzt+1)    !:
    1678     REAL(wp) ::  sums_ll(nzb:nzt+1,2)  !:
     1658    REAL(wp) ::  dptdz_threshold  !<
     1659    REAL(wp) ::  fac              !<
     1660    REAL(wp) ::  height           !<
     1661    REAL(wp) ::  pts              !<
     1662    REAL(wp) ::  sums_l_eper      !<
     1663    REAL(wp) ::  sums_l_etot      !<
     1664    REAL(wp) ::  s1               !<
     1665    REAL(wp) ::  s2               !<
     1666    REAL(wp) ::  s3               !<
     1667    REAL(wp) ::  s4               !<
     1668    REAL(wp) ::  s5               !<
     1669    REAL(wp) ::  s6               !<
     1670    REAL(wp) ::  s7               !<
     1671    REAL(wp) ::  ust              !<
     1672    REAL(wp) ::  ust2             !<
     1673    REAL(wp) ::  u2               !<
     1674    REAL(wp) ::  vst              !<
     1675    REAL(wp) ::  vst2             !<
     1676    REAL(wp) ::  v2               !<
     1677    REAL(wp) ::  w2               !<
     1678    REAL(wp) ::  z_i(2)           !<
     1679
     1680    REAL(wp) ::  dptdz(nzb+1:nzt+1)    !<
     1681    REAL(wp) ::  sums_ll(nzb:nzt+1,2)  !<
    16791682
    16801683    CALL cpu_log( log_point(10), 'flow_statistics', 'start' )
Note: See TracChangeset for help on using the changeset viewer.