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

    r1354 r1682  
    1  SUBROUTINE user_3d_data_averaging( mode, variable )
    2 
     1!> @file user_3d_data_averaging.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4746! Description:
    4847! ------------
    49 ! Sum up and time-average user-defined output quantities as well as allocate
    50 ! the array necessary for storing the average.
     48!> Sum up and time-average user-defined output quantities as well as allocate
     49!> the array necessary for storing the average.
    5150!------------------------------------------------------------------------------!
     51 SUBROUTINE user_3d_data_averaging( mode, variable )
     52 
    5253
    5354    USE control_parameters
     
    6162    IMPLICIT NONE
    6263
    63     CHARACTER (LEN=*) ::  mode    !:
    64     CHARACTER (LEN=*) :: variable !:
     64    CHARACTER (LEN=*) ::  mode    !<
     65    CHARACTER (LEN=*) :: variable !<
    6566
    66     INTEGER(iwp) ::  i !:
    67     INTEGER(iwp) ::  j !:
    68     INTEGER(iwp) ::  k !:
     67    INTEGER(iwp) ::  i !<
     68    INTEGER(iwp) ::  j !<
     69    INTEGER(iwp) ::  k !<
    6970
    7071    IF ( mode == 'allocate' )  THEN
Note: See TracChangeset for help on using the changeset viewer.