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

    r1354 r1682  
    1  SUBROUTINE init_pt_anomaly
    2 
     1!> @file init_pt_anomaly.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5251! Description:
    5352! ------------
    54 ! Impose a temperature perturbation for an advection test.
     53!> Impose a temperature perturbation for an advection test.
    5554!------------------------------------------------------------------------------!
     55 SUBROUTINE init_pt_anomaly
     56 
    5657
    5758    USE arrays_3d,                                                             &
     
    6869    IMPLICIT NONE
    6970
    70     INTEGER(iwp) ::  i  !:
    71     INTEGER(iwp) ::  ic !:
    72     INTEGER(iwp) ::  j  !:
    73     INTEGER(iwp) ::  jc !:
    74     INTEGER(iwp) ::  k  !:
    75     INTEGER(iwp) ::  kc !:
     71    INTEGER(iwp) ::  i  !<
     72    INTEGER(iwp) ::  ic !<
     73    INTEGER(iwp) ::  j  !<
     74    INTEGER(iwp) ::  jc !<
     75    INTEGER(iwp) ::  k  !<
     76    INTEGER(iwp) ::  kc !<
    7677   
    77     REAL(wp)     ::  betrag !:
    78     REAL(wp)     ::  radius !:
    79     REAL(wp)     ::  rc     !:
    80     REAL(wp)     ::  x      !:
    81     REAL(wp)     ::  y      !:
    82     REAL(wp)     ::  z      !:
     78    REAL(wp)     ::  betrag !<
     79    REAL(wp)     ::  radius !<
     80    REAL(wp)     ::  rc     !<
     81    REAL(wp)     ::  x      !<
     82    REAL(wp)     ::  y      !<
     83    REAL(wp)     ::  z      !<
    8384   
    8485!
Note: See TracChangeset for help on using the changeset viewer.