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/user_statistics.f90

    r1354 r1682  
    1  SUBROUTINE user_statistics( mode, sr, tn )
    2 
     1!> @file user_statistics.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4847! Description:
    4948! ------------
    50 ! Calculation of user-defined statistics, i.e. horizontally averaged profiles
    51 ! and time series.
    52 ! This routine is called for every statistic region sr defined by the user,
    53 ! but at least for the region "total domain" (sr=0).
    54 ! See section 3.5.4 on how to define, calculate, and output user defined
    55 ! quantities.
     49!> Calculation of user-defined statistics, i.e. horizontally averaged profiles
     50!> and time series.
     51!> This routine is called for every statistic region sr defined by the user,
     52!> but at least for the region "total domain" (sr=0).
     53!> See section 3.5.4 on how to define, calculate, and output user defined
     54!> quantities.
    5655!------------------------------------------------------------------------------!
     56 SUBROUTINE user_statistics( mode, sr, tn )
     57 
    5758
    5859    USE arrays_3d
     
    7273    IMPLICIT NONE
    7374
    74     CHARACTER (LEN=*) ::  mode   !:
     75    CHARACTER (LEN=*) ::  mode   !<
    7576
    76     INTEGER(iwp) ::  i    !:
    77     INTEGER(iwp) ::  j    !:
    78     INTEGER(iwp) ::  k    !:
    79     INTEGER(iwp) ::  sr   !:
    80     INTEGER(iwp) ::  tn   !:
     77    INTEGER(iwp) ::  i    !<
     78    INTEGER(iwp) ::  j    !<
     79    INTEGER(iwp) ::  k    !<
     80    INTEGER(iwp) ::  sr   !<
     81    INTEGER(iwp) ::  tn   !<
    8182
    8283    REAL(wp),                                                                  &
    8384       DIMENSION(dots_num_palm+1:dots_max) ::                                  &
    84           ts_value_l   !:
     85          ts_value_l   !<
    8586
    8687
Note: See TracChangeset for help on using the changeset viewer.