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

    r1321 r1682  
    1  SUBROUTINE local_getenv( var, ivar, value, ivalue )
    2 
     1!> @file local_getenv.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322! Former revisions:
    2423! -----------------
     
    4241! Description:
    4342! ------------
    44 ! Getting the values of environment-variabls (for different operating-systems)
     43!> Getting the values of environment-variabls (for different operating-systems)
    4544!------------------------------------------------------------------------------!
     45 SUBROUTINE local_getenv( var, ivar, value, ivalue )
     46 
    4647
    4748    USE kinds
     
    5051    USE pegrid
    5152#endif
    52     CHARACTER (LEN=*) ::  value  !:
    53     CHARACTER (LEN=*) ::  var    !:
     53    CHARACTER (LEN=*) ::  value  !<
     54    CHARACTER (LEN=*) ::  var    !<
    5455   
    55     INTEGER(iwp)      ::  ivalue !:
    56     INTEGER(iwp)      ::  ivar   !:
     56    INTEGER(iwp)      ::  ivalue !<
     57    INTEGER(iwp)      ::  ivar   !<
    5758#if defined( __lcmuk )
    58     INTEGER(iwp)      ::  i      !:
    59     INTEGER(iwp)      ::  ia(20) !:
     59    INTEGER(iwp)      ::  i      !<
     60    INTEGER(iwp)      ::  ia(20) !<
    6061#endif
    6162
Note: See TracChangeset for help on using the changeset viewer.