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

    r1354 r1682  
    1  MODULE calc_precipitation_mod
    2 
     1!> @file calc_precipitation.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! -----------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    4746! Description:
    4847! ------------
    49 ! Calculate the change of total water content due to precipitation
    50 ! (simplified Kessler scheme)
     48!> Calculate the change of total water content due to precipitation
     49!> (simplified Kessler scheme)
    5150!------------------------------------------------------------------------------!
     51 MODULE calc_precipitation_mod
     52 
    5253
    5354    PRIVATE
     
    6364
    6465!------------------------------------------------------------------------------!
    65 ! Call for all grid points
     66! Description:
     67! ------------
     68!> Call for all grid points
    6669!------------------------------------------------------------------------------!
    6770    SUBROUTINE calc_precipitation
     
    8790       IMPLICIT NONE
    8891
    89        INTEGER(iwp) ::  i !:
    90        INTEGER(iwp) ::  j !:
    91        INTEGER(iwp) ::  k !:
     92       INTEGER(iwp) ::  i !<
     93       INTEGER(iwp) ::  j !<
     94       INTEGER(iwp) ::  k !<
    9295       
    93        REAL(wp)    ::  dqdt_precip !:
     96       REAL(wp)    ::  dqdt_precip !<
    9497
    9598       precipitation_rate = 0.0_wp
     
    127130
    128131!------------------------------------------------------------------------------!
    129 ! Call for grid point i,j
     132! Description:
     133! ------------
     134!> Call for grid point i,j
    130135!------------------------------------------------------------------------------!
    131136    SUBROUTINE calc_precipitation_ij( i, j )
     
    151156       IMPLICIT NONE
    152157
    153        INTEGER(iwp) ::  i !:
    154        INTEGER(iwp) ::  j !:
    155        INTEGER(iwp) ::  k !:
     158       INTEGER(iwp) ::  i !<
     159       INTEGER(iwp) ::  j !<
     160       INTEGER(iwp) ::  k !<
    156161       
    157        REAL(wp)    ::  dqdt_precip !:       
     162       REAL(wp)    ::  dqdt_precip !<       
    158163
    159164       precipitation_rate(j,i) = 0.0_wp
Note: See TracChangeset for help on using the changeset viewer.