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

    r1360 r1682  
    1  SUBROUTINE lpm_set_attributes
    2 
     1!> @file lpm_set_attributes.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5554! Description:
    5655! ------------
    57 ! This routine sets certain particle attributes depending on the values that
    58 ! other PALM variables have at the current particle position.
     56!> This routine sets certain particle attributes depending on the values that
     57!> other PALM variables have at the current particle position.
    5958!------------------------------------------------------------------------------!
     59 SUBROUTINE lpm_set_attributes
     60 
    6061
    6162    USE arrays_3d,                                                             &
     
    9192    IMPLICIT NONE
    9293
    93     INTEGER(iwp) ::  i        !:
    94     INTEGER(iwp) ::  ip       !:
    95     INTEGER(iwp) ::  j        !:
    96     INTEGER(iwp) ::  jp       !:
    97     INTEGER(iwp) ::  k        !:
    98     INTEGER(iwp) ::  kp       !:
    99     INTEGER(iwp) ::  n        !:
    100     INTEGER(iwp) ::  nb       !:
    101 
    102     INTEGER(iwp), DIMENSION(0:7) ::  start_index !:
    103     INTEGER(iwp), DIMENSION(0:7) ::  end_index   !:
    104 
    105     REAL(wp)    ::  aa        !:
    106     REAL(wp)    ::  absuv     !:
    107     REAL(wp)    ::  bb        !:
    108     REAL(wp)    ::  cc        !:
    109     REAL(wp)    ::  dd        !:
    110     REAL(wp)    ::  gg        !:
    111     REAL(wp)    ::  height    !:
    112     REAL(wp)    ::  pt_int    !:
    113     REAL(wp)    ::  pt_int_l  !:
    114     REAL(wp)    ::  pt_int_u  !:
    115     REAL(wp)    ::  u_int_l   !:
    116     REAL(wp)    ::  u_int_u   !:
    117     REAL(wp)    ::  v_int_l   !:
    118     REAL(wp)    ::  v_int_u   !:
    119     REAL(wp)    ::  w_int     !:
    120     REAL(wp)    ::  w_int_l   !:
    121     REAL(wp)    ::  w_int_u   !:
    122     REAL(wp)    ::  x         !:
    123     REAL(wp)    ::  y         !:
    124 
    125     REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_int                  !:
    126     REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_int                  !:
    127     REAL(wp), DIMENSION(:), ALLOCATABLE ::  xv                     !:
    128     REAL(wp), DIMENSION(:), ALLOCATABLE ::  yv                     !:
    129     REAL(wp), DIMENSION(:), ALLOCATABLE ::  zv                     !:
     94    INTEGER(iwp) ::  i        !<
     95    INTEGER(iwp) ::  ip       !<
     96    INTEGER(iwp) ::  j        !<
     97    INTEGER(iwp) ::  jp       !<
     98    INTEGER(iwp) ::  k        !<
     99    INTEGER(iwp) ::  kp       !<
     100    INTEGER(iwp) ::  n        !<
     101    INTEGER(iwp) ::  nb       !<
     102
     103    INTEGER(iwp), DIMENSION(0:7) ::  start_index !<
     104    INTEGER(iwp), DIMENSION(0:7) ::  end_index   !<
     105
     106    REAL(wp)    ::  aa        !<
     107    REAL(wp)    ::  absuv     !<
     108    REAL(wp)    ::  bb        !<
     109    REAL(wp)    ::  cc        !<
     110    REAL(wp)    ::  dd        !<
     111    REAL(wp)    ::  gg        !<
     112    REAL(wp)    ::  height    !<
     113    REAL(wp)    ::  pt_int    !<
     114    REAL(wp)    ::  pt_int_l  !<
     115    REAL(wp)    ::  pt_int_u  !<
     116    REAL(wp)    ::  u_int_l   !<
     117    REAL(wp)    ::  u_int_u   !<
     118    REAL(wp)    ::  v_int_l   !<
     119    REAL(wp)    ::  v_int_u   !<
     120    REAL(wp)    ::  w_int     !<
     121    REAL(wp)    ::  w_int_l   !<
     122    REAL(wp)    ::  w_int_u   !<
     123    REAL(wp)    ::  x         !<
     124    REAL(wp)    ::  y         !<
     125
     126    REAL(wp), DIMENSION(:), ALLOCATABLE ::  u_int                  !<
     127    REAL(wp), DIMENSION(:), ALLOCATABLE ::  v_int                  !<
     128    REAL(wp), DIMENSION(:), ALLOCATABLE ::  xv                     !<
     129    REAL(wp), DIMENSION(:), ALLOCATABLE ::  yv                     !<
     130    REAL(wp), DIMENSION(:), ALLOCATABLE ::  zv                     !<
    130131
    131132    CALL cpu_log( log_point_s(49), 'lpm_set_attributes', 'start' )
Note: See TracChangeset for help on using the changeset viewer.