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

    r1375 r1682  
    1  SUBROUTINE diffusivities( var, var_reference )
    2 
     1!> @file diffusivities.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    6362! Description:
    6463! ------------
    65 ! Computation of the turbulent diffusion coefficients for momentum and heat
    66 ! according to Prandtl-Kolmogorov
     64!> Computation of the turbulent diffusion coefficients for momentum and heat
     65!> according to Prandtl-Kolmogorov
    6766!------------------------------------------------------------------------------!
     67 SUBROUTINE diffusivities( var, var_reference )
     68 
    6869
    6970    USE arrays_3d,                                                             &
     
    8586    IMPLICIT NONE
    8687
    87     INTEGER(iwp) ::  i                   !:
    88     INTEGER(iwp) ::  j                   !:
    89     INTEGER(iwp) ::  k                   !:
    90     INTEGER(iwp) ::  omp_get_thread_num  !:
    91     INTEGER(iwp) ::  sr                  !:
    92     INTEGER(iwp) ::  tn                  !:
    93 
    94     REAL(wp)     ::  dvar_dz             !:
    95     REAL(wp)     ::  l                   !:
    96     REAL(wp)     ::  ll                  !:
    97     REAL(wp)     ::  l_stable            !:
    98     REAL(wp)     ::  sqrt_e              !:
    99     REAL(wp)     ::  var_reference       !:
    100 
    101     REAL(wp)     ::  var(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !:
     88    INTEGER(iwp) ::  i                   !<
     89    INTEGER(iwp) ::  j                   !<
     90    INTEGER(iwp) ::  k                   !<
     91    INTEGER(iwp) ::  omp_get_thread_num  !<
     92    INTEGER(iwp) ::  sr                  !<
     93    INTEGER(iwp) ::  tn                  !<
     94
     95    REAL(wp)     ::  dvar_dz             !<
     96    REAL(wp)     ::  l                   !<
     97    REAL(wp)     ::  ll                  !<
     98    REAL(wp)     ::  l_stable            !<
     99    REAL(wp)     ::  sqrt_e              !<
     100    REAL(wp)     ::  var_reference       !<
     101
     102    REAL(wp)     ::  var(nzb:nzt+1,nysg:nyng,nxlg:nxrg)  !<
    102103
    103104
Note: See TracChangeset for help on using the changeset viewer.