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

    r1360 r1682  
    1  SUBROUTINE lpm_release_set
    2 
     1!> @file lpm_release_set.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5049! Description:
    5150! ------------
    52 ! Release a new set of particles and, if required, particle tails. These
    53 ! particles/tails are added at the end of the existing arrays. Extend the
    54 ! respective particle and tail arrays, if neccessary.
     51!> Release a new set of particles and, if required, particle tails. These
     52!> particles/tails are added at the end of the existing arrays. Extend the
     53!> respective particle and tail arrays, if neccessary.
    5554!------------------------------------------------------------------------------!
     55 SUBROUTINE lpm_release_set
     56 
    5657
    5758    USE control_parameters,                                                    &
     
    7576    IMPLICIT NONE
    7677
    77     INTEGER(iwp) ::  ie     !:
    78     INTEGER(iwp) ::  is     !:
    79     INTEGER(iwp) ::  n      !:
    80     INTEGER(iwp) ::  nn     !:
     78    INTEGER(iwp) ::  ie     !<
     79    INTEGER(iwp) ::  is     !<
     80    INTEGER(iwp) ::  n      !<
     81    INTEGER(iwp) ::  nn     !<
    8182
    8283
Note: See TracChangeset for help on using the changeset viewer.