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

    r1360 r1682  
    1  SUBROUTINE lpm_droplet_collision (i,j,k)
    2 
     1!> @file lpm_droplet_collision.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    5958! Description:
    6059! ------------
    61 ! Calculates change in droplet radius by collision. Droplet collision is
    62 ! calculated for each grid box seperately. Collision is parameterized by
    63 ! using collision kernels. Three different kernels are available:
    64 ! PALM kernel: Kernel is approximated using a method from Rogers and
    65 !              Yau (1989, A Short Course in Cloud Physics, Pergamon Press).
    66 !              All droplets smaller than the treated one are represented by
    67 !              one droplet with mean features. Collision efficiencies are taken
    68 !              from the respective table in Rogers and Yau.
    69 ! Hall kernel: Kernel from Hall (1980, J. Atmos. Sci., 2486-2507), which
    70 !              considers collision due to pure gravitational effects.
    71 ! Wang kernel: Beside gravitational effects (treated with the Hall-kernel) also
    72 !              the effects of turbulence on the collision are considered using
    73 !              parameterizations of Ayala et al. (2008, New J. Phys., 10,
    74 !              075015) and Wang and Grabowski (2009, Atmos. Sci. Lett., 10,
    75 !              1-8). This kernel includes three possible effects of turbulence:
    76 !              the modification of the relative velocity between the droplets,
    77 !              the effect of preferential concentration, and the enhancement of
    78 !              collision efficiencies.
     60!> Calculates change in droplet radius by collision. Droplet collision is
     61!> calculated for each grid box seperately. Collision is parameterized by
     62!> using collision kernels. Three different kernels are available:
     63!> PALM kernel: Kernel is approximated using a method from Rogers and
     64!>              Yau (1989, A Short Course in Cloud Physics, Pergamon Press).
     65!>              All droplets smaller than the treated one are represented by
     66!>              one droplet with mean features. Collision efficiencies are taken
     67!>              from the respective table in Rogers and Yau.
     68!> Hall kernel: Kernel from Hall (1980, J. Atmos. Sci., 2486-2507), which
     69!>              considers collision due to pure gravitational effects.
     70!> Wang kernel: Beside gravitational effects (treated with the Hall-kernel) also
     71!>              the effects of turbulence on the collision are considered using
     72!>              parameterizations of Ayala et al. (2008, New J. Phys., 10,
     73!>              075015) and Wang and Grabowski (2009, Atmos. Sci. Lett., 10,
     74!>              1-8). This kernel includes three possible effects of turbulence:
     75!>              the modification of the relative velocity between the droplets,
     76!>              the effect of preferential concentration, and the enhancement of
     77!>              collision efficiencies.
    7978!------------------------------------------------------------------------------!
     79 SUBROUTINE lpm_droplet_collision (i,j,k)
     80 
    8081
    8182
     
    115116    IMPLICIT NONE
    116117
    117     INTEGER(iwp) ::  eclass   !:
    118     INTEGER(iwp) ::  i        !:
    119     INTEGER(iwp) ::  ii       !:
    120     INTEGER(iwp) ::  inc      !:
    121     INTEGER(iwp) ::  is       !:
    122     INTEGER(iwp) ::  j        !:
    123     INTEGER(iwp) ::  jj       !:
    124     INTEGER(iwp) ::  js       !:
    125     INTEGER(iwp) ::  k        !:
    126     INTEGER(iwp) ::  kk       !:
    127     INTEGER(iwp) ::  n        !:
    128     INTEGER(iwp) ::  pse      !:
    129     INTEGER(iwp) ::  psi      !:
    130     INTEGER(iwp) ::  rclass_l !:
    131     INTEGER(iwp) ::  rclass_s !:
    132 
    133     INTEGER(iwp), DIMENSION(prt_count(k,j,i)) ::  rclass_v !:
    134 
    135     LOGICAL, SAVE ::  first_flag = .TRUE. !:
    136 
    137     TYPE(particle_type) :: tmp_particle   !:
    138 
    139     REAL(wp) ::  aa       !:
    140     REAL(wp) ::  auxn     !: temporary variables
    141     REAL(wp) ::  auxs     !: temporary variables
    142     REAL(wp) ::  bb       !:
    143     REAL(wp) ::  cc       !:
    144     REAL(wp) ::  dd       !:
    145     REAL(wp) ::  ddV      !:
    146     REAL(wp) ::  delta_r  !:
    147     REAL(wp) ::  delta_v  !:
    148     REAL(wp) ::  epsilon  !:
    149     REAL(wp) ::  gg       !:
    150     REAL(wp) ::  mean_r   !:
    151     REAL(wp) ::  ql_int   !:
    152     REAL(wp) ::  ql_int_l !:
    153     REAL(wp) ::  ql_int_u !:
    154     REAL(wp) ::  r3       !:
    155     REAL(wp) ::  sl_r3    !:
    156     REAL(wp) ::  sl_r4    !:
    157     REAL(wp) ::  sum1     !:
    158     REAL(wp) ::  sum2     !:
    159     REAL(wp) ::  sum3     !:
    160     REAL(wp) ::  u_int    !:
    161     REAL(wp) ::  u_int_l  !:
    162     REAL(wp) ::  u_int_u  !:
    163     REAL(wp) ::  v_int    !:
    164     REAL(wp) ::  v_int_l  !:
    165     REAL(wp) ::  v_int_u  !:
    166     REAL(wp) ::  w_int    !:
    167     REAL(wp) ::  w_int_l  !:
    168     REAL(wp) ::  w_int_u  !:
    169     REAL(wp) ::  x        !:
    170     REAL(wp) ::  y        !:
    171 
    172     REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad    !:
    173     REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight !:
     118    INTEGER(iwp) ::  eclass   !<
     119    INTEGER(iwp) ::  i        !<
     120    INTEGER(iwp) ::  ii       !<
     121    INTEGER(iwp) ::  inc      !<
     122    INTEGER(iwp) ::  is       !<
     123    INTEGER(iwp) ::  j        !<
     124    INTEGER(iwp) ::  jj       !<
     125    INTEGER(iwp) ::  js       !<
     126    INTEGER(iwp) ::  k        !<
     127    INTEGER(iwp) ::  kk       !<
     128    INTEGER(iwp) ::  n        !<
     129    INTEGER(iwp) ::  pse      !<
     130    INTEGER(iwp) ::  psi      !<
     131    INTEGER(iwp) ::  rclass_l !<
     132    INTEGER(iwp) ::  rclass_s !<
     133
     134    INTEGER(iwp), DIMENSION(prt_count(k,j,i)) ::  rclass_v !<
     135
     136    LOGICAL, SAVE ::  first_flag = .TRUE. !<
     137
     138    TYPE(particle_type) :: tmp_particle   !<
     139
     140    REAL(wp) ::  aa       !<
     141    REAL(wp) ::  auxn     !< temporary variables
     142    REAL(wp) ::  auxs     !< temporary variables
     143    REAL(wp) ::  bb       !<
     144    REAL(wp) ::  cc       !<
     145    REAL(wp) ::  dd       !<
     146    REAL(wp) ::  ddV      !<
     147    REAL(wp) ::  delta_r  !<
     148    REAL(wp) ::  delta_v  !<
     149    REAL(wp) ::  epsilon  !<
     150    REAL(wp) ::  gg       !<
     151    REAL(wp) ::  mean_r   !<
     152    REAL(wp) ::  ql_int   !<
     153    REAL(wp) ::  ql_int_l !<
     154    REAL(wp) ::  ql_int_u !<
     155    REAL(wp) ::  r3       !<
     156    REAL(wp) ::  sl_r3    !<
     157    REAL(wp) ::  sl_r4    !<
     158    REAL(wp) ::  sum1     !<
     159    REAL(wp) ::  sum2     !<
     160    REAL(wp) ::  sum3     !<
     161    REAL(wp) ::  u_int    !<
     162    REAL(wp) ::  u_int_l  !<
     163    REAL(wp) ::  u_int_u  !<
     164    REAL(wp) ::  v_int    !<
     165    REAL(wp) ::  v_int_l  !<
     166    REAL(wp) ::  v_int_u  !<
     167    REAL(wp) ::  w_int    !<
     168    REAL(wp) ::  w_int_l  !<
     169    REAL(wp) ::  w_int_u  !<
     170    REAL(wp) ::  x        !<
     171    REAL(wp) ::  y        !<
     172
     173    REAL(wp), DIMENSION(:), ALLOCATABLE ::  rad    !<
     174    REAL(wp), DIMENSION(:), ALLOCATABLE ::  weight !<
    174175
    175176    REAL, DIMENSION(prt_count(k,j,i))    :: ck
Note: See TracChangeset for help on using the changeset viewer.