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

    r1552 r1682  
    1  SUBROUTINE prandtl_fluxes
    2 
     1!> @file prandtl_fluxes.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    7776! Description:
    7877! ------------
    79 ! Diagnostic computation of vertical fluxes in the Prandtl layer from the
    80 ! values of the variables at grid point k=1
     78!> Diagnostic computation of vertical fluxes in the Prandtl layer from the
     79!> values of the variables at grid point k=1
    8180!------------------------------------------------------------------------------!
     81 SUBROUTINE prandtl_fluxes
     82 
    8283
    8384    USE arrays_3d,                                                             &
     
    100101    IMPLICIT NONE
    101102
    102     INTEGER(iwp) ::  i            !:
    103     INTEGER(iwp) ::  j            !:
    104     INTEGER(iwp) ::  k            !:
    105 
    106     LOGICAL      ::  coupled_run  !:
    107 
    108     REAL(wp)     ::  a            !:
    109     REAL(wp)     ::  b            !:
    110     REAL(wp)     ::  e_q          !:
    111     REAL(wp)     ::  rifm         !:
    112     REAL(wp)     ::  uv_total     !:
    113     REAL(wp)     ::  z_p          !:
     103    INTEGER(iwp) ::  i            !<
     104    INTEGER(iwp) ::  j            !<
     105    INTEGER(iwp) ::  k            !<
     106
     107    LOGICAL      ::  coupled_run  !<
     108
     109    REAL(wp)     ::  a            !<
     110    REAL(wp)     ::  b            !<
     111    REAL(wp)     ::  e_q          !<
     112    REAL(wp)     ::  rifm         !<
     113    REAL(wp)     ::  uv_total     !<
     114    REAL(wp)     ::  z_p          !<
    114115
    115116!
Note: See TracChangeset for help on using the changeset viewer.