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

    r1354 r1682  
    1  SUBROUTINE init_slope
    2 
     1!> @file init_slope.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4948! Description:
    5049! ------------
    51 ! Initialization of the temperature field and other variables used in case
    52 ! of a sloping surface.
    53 ! Remember: when a sloping surface is used, only one constant temperature
    54 !           gradient is allowed!
     50!> Initialization of the temperature field and other variables used in case
     51!> of a sloping surface.
     52!> @note when a sloping surface is used, only one constant temperature
     53!>       gradient is allowed!
    5554!------------------------------------------------------------------------------!
     55 SUBROUTINE init_slope
     56 
    5657
    5758    USE arrays_3d,                                                             &
     
    7879    IMPLICIT NONE
    7980
    80     INTEGER(iwp) ::  i        !:
    81     INTEGER(iwp) ::  j        !:
    82     INTEGER(iwp) ::  k        !:
     81    INTEGER(iwp) ::  i        !<
     82    INTEGER(iwp) ::  j        !<
     83    INTEGER(iwp) ::  k        !<
    8384   
    84     REAL(wp)     ::  alpha    !:
    85     REAL(wp)     ::  height   !:
    86     REAL(wp)     ::  pt_value !:
    87     REAL(wp)     ::  radius   !:
     85    REAL(wp)     ::  alpha    !<
     86    REAL(wp)     ::  height   !<
     87    REAL(wp)     ::  pt_value !<
     88    REAL(wp)     ::  radius   !<
    8889   
    89     REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init_local !:
     90    REAL(wp), DIMENSION(:), ALLOCATABLE ::  pt_init_local !<
    9091
    9192!
Note: See TracChangeset for help on using the changeset viewer.