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

    r1360 r1682  
    1  SUBROUTINE lpm_droplet_condensation (ip,jp,kp)
    2 
     1!> @file lpm_droplet_condensation.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    7170! Description:
    7271! ------------
    73 ! Calculates change in droplet radius by condensation/evaporation, using
    74 ! either an analytic formula or by numerically integrating the radius growth
    75 ! equation including curvature and solution effects using Rosenbrocks method
    76 ! (see Numerical recipes in FORTRAN, 2nd edition, p. 731).
    77 ! The analytical formula and growth equation follow those given in
    78 ! Rogers and Yau (A short course in cloud physics, 3rd edition, p. 102/103).
     72!> Calculates change in droplet radius by condensation/evaporation, using
     73!> either an analytic formula or by numerically integrating the radius growth
     74!> equation including curvature and solution effects using Rosenbrocks method
     75!> (see Numerical recipes in FORTRAN, 2nd edition, p. 731).
     76!> The analytical formula and growth equation follow those given in
     77!> Rogers and Yau (A short course in cloud physics, 3rd edition, p. 102/103).
    7978!------------------------------------------------------------------------------!
     79 SUBROUTINE lpm_droplet_condensation (ip,jp,kp)
     80 
    8081
    8182    USE arrays_3d,                                                             &
     
    111112    IMPLICIT NONE
    112113
    113     INTEGER(iwp) :: i                          !:
    114     INTEGER(iwp) :: ip                         !:
    115     INTEGER(iwp) :: internal_timestep_count    !:
    116     INTEGER(iwp) :: j                          !:
    117     INTEGER(iwp) :: jp                         !:
    118     INTEGER(iwp) :: jtry                       !:
    119     INTEGER(iwp) :: k                          !:
    120     INTEGER(iwp) :: kp                         !:
    121     INTEGER(iwp) :: n                          !:
    122     INTEGER(iwp) :: nb                         !:
    123     INTEGER(iwp) :: ros_count                  !:
     114    INTEGER(iwp) :: i                          !<
     115    INTEGER(iwp) :: ip                         !<
     116    INTEGER(iwp) :: internal_timestep_count    !<
     117    INTEGER(iwp) :: j                          !<
     118    INTEGER(iwp) :: jp                         !<
     119    INTEGER(iwp) :: jtry                       !<
     120    INTEGER(iwp) :: k                          !<
     121    INTEGER(iwp) :: kp                         !<
     122    INTEGER(iwp) :: n                          !<
     123    INTEGER(iwp) :: nb                         !<
     124    INTEGER(iwp) :: ros_count                  !<
    124125 
    125     INTEGER(iwp), PARAMETER ::  maxtry = 40      !:
    126 
    127     INTEGER(iwp), DIMENSION(0:7) ::  end_index   !:
    128     INTEGER(iwp), DIMENSION(0:7) ::  start_index !:
    129 
    130     LOGICAL ::  repeat                           !:
    131 
    132     LOGICAL, DIMENSION(number_of_particles) ::  flag_1 !:
    133 
    134     REAL(wp) ::  aa                            !:
    135     REAL(wp) ::  afactor                       !:
    136     REAL(wp) ::  arg                           !:
    137     REAL(wp) ::  bb                            !:
    138     REAL(wp) ::  cc                            !:
    139     REAL(wp) ::  dd                            !:
    140     REAL(wp) ::  ddenom                        !:
    141     REAL(wp) ::  delta_r                       !:
    142     REAL(wp) ::  drdt                          !:
    143     REAL(wp) ::  drdt_ini                      !:
    144     REAL(wp) ::  dt_ros                        !:
    145     REAL(wp) ::  dt_ros_next                   !:
    146     REAL(wp) ::  dt_ros_sum                    !:
    147     REAL(wp) ::  dt_ros_sum_ini                !:
    148     REAL(wp) ::  d2rdtdr                       !:
    149     REAL(wp) ::  errmax                        !:
    150     REAL(wp) ::  err_ros                       !:
    151     REAL(wp) ::  g1                            !:
    152     REAL(wp) ::  g2                            !:
    153     REAL(wp) ::  g3                            !:
    154     REAL(wp) ::  g4                            !:
    155     REAL(wp) ::  gg                            !:
    156     REAL(wp) ::  pt_int                        !:
    157     REAL(wp) ::  pt_int_l                      !:
    158     REAL(wp) ::  pt_int_u                      !:
    159     REAL(wp) ::  q_int                         !:
    160     REAL(wp) ::  q_int_l                       !:
    161     REAL(wp) ::  q_int_u                       !:
    162     REAL(wp) ::  r_ros                         !:
    163     REAL(wp) ::  r_ros_ini                     !:
    164     REAL(wp) ::  sigma                         !:
    165     REAL(wp) ::  x                             !:
    166     REAL(wp) ::  y                             !:
    167     REAL(wp) ::  re_p                          !:
     126    INTEGER(iwp), PARAMETER ::  maxtry = 40      !<
     127
     128    INTEGER(iwp), DIMENSION(0:7) ::  end_index   !<
     129    INTEGER(iwp), DIMENSION(0:7) ::  start_index !<
     130
     131    LOGICAL ::  repeat                           !<
     132
     133    LOGICAL, DIMENSION(number_of_particles) ::  flag_1 !<
     134
     135    REAL(wp) ::  aa                            !<
     136    REAL(wp) ::  afactor                       !<
     137    REAL(wp) ::  arg                           !<
     138    REAL(wp) ::  bb                            !<
     139    REAL(wp) ::  cc                            !<
     140    REAL(wp) ::  dd                            !<
     141    REAL(wp) ::  ddenom                        !<
     142    REAL(wp) ::  delta_r                       !<
     143    REAL(wp) ::  drdt                          !<
     144    REAL(wp) ::  drdt_ini                      !<
     145    REAL(wp) ::  dt_ros                        !<
     146    REAL(wp) ::  dt_ros_next                   !<
     147    REAL(wp) ::  dt_ros_sum                    !<
     148    REAL(wp) ::  dt_ros_sum_ini                !<
     149    REAL(wp) ::  d2rdtdr                       !<
     150    REAL(wp) ::  errmax                        !<
     151    REAL(wp) ::  err_ros                       !<
     152    REAL(wp) ::  g1                            !<
     153    REAL(wp) ::  g2                            !<
     154    REAL(wp) ::  g3                            !<
     155    REAL(wp) ::  g4                            !<
     156    REAL(wp) ::  gg                            !<
     157    REAL(wp) ::  pt_int                        !<
     158    REAL(wp) ::  pt_int_l                      !<
     159    REAL(wp) ::  pt_int_u                      !<
     160    REAL(wp) ::  q_int                         !<
     161    REAL(wp) ::  q_int_l                       !<
     162    REAL(wp) ::  q_int_u                       !<
     163    REAL(wp) ::  r_ros                         !<
     164    REAL(wp) ::  r_ros_ini                     !<
     165    REAL(wp) ::  sigma                         !<
     166    REAL(wp) ::  x                             !<
     167    REAL(wp) ::  y                             !<
     168    REAL(wp) ::  re_p                          !<
    168169 
    169170!-- Parameters for Rosenbrock method
    170     REAL(wp), PARAMETER ::  a21 = 2.0_wp               !:
    171     REAL(wp), PARAMETER ::  a31 = 48.0_wp / 25.0_wp    !:
    172     REAL(wp), PARAMETER ::  a32 = 6.0_wp / 25.0_wp     !:
    173     REAL(wp), PARAMETER ::  b1 = 19.0_wp / 9.0_wp      !:
    174     REAL(wp), PARAMETER ::  b2 = 0.5_wp                !:
    175     REAL(wp), PARAMETER ::  b3 = 25.0_wp / 108.0_wp    !:
    176     REAL(wp), PARAMETER ::  b4 = 125.0_wp / 108.0_wp   !:
    177     REAL(wp), PARAMETER ::  c21 = -8.0_wp              !:
    178     REAL(wp), PARAMETER ::  c31 = 372.0_wp / 25.0_wp   !:
    179     REAL(wp), PARAMETER ::  c32 = 12.0_wp / 5.0_wp     !:
    180     REAL(wp), PARAMETER ::  c41 = -112.0_wp / 125.0_wp !:
    181     REAL(wp), PARAMETER ::  c42 = -54.0_wp / 125.0_wp  !:
    182     REAL(wp), PARAMETER ::  c43 = -2.0_wp / 5.0_wp     !:
    183     REAL(wp), PARAMETER ::  errcon = 0.1296_wp         !:
    184     REAL(wp), PARAMETER ::  e1 = 17.0_wp / 54.0_wp     !:
    185     REAL(wp), PARAMETER ::  e2 = 7.0_wp / 36.0_wp      !:
    186     REAL(wp), PARAMETER ::  e3 = 0.0_wp                !:
    187     REAL(wp), PARAMETER ::  e4 = 125.0_wp / 108.0_wp   !:
    188     REAL(wp), PARAMETER ::  gam = 0.5_wp               !:
    189     REAL(wp), PARAMETER ::  grow = 1.5_wp              !:
    190     REAL(wp), PARAMETER ::  pgrow = -0.25_wp           !:
    191     REAL(wp), PARAMETER ::  pshrnk = -1.0_wp /3.0_wp   !:
    192     REAL(wp), PARAMETER ::  shrnk = 0.5_wp             !:
    193 
    194     REAL(wp), DIMENSION(number_of_particles) ::  afactor_v              !:
    195     REAL(wp), DIMENSION(number_of_particles) ::  diff_coeff_v           !:
    196     REAL(wp), DIMENSION(number_of_particles) ::  e_s                    !:
    197     REAL(wp), DIMENSION(number_of_particles) ::  e_a                    !:
    198     REAL(wp), DIMENSION(number_of_particles) ::  new_r                  !:
    199     REAL(wp), DIMENSION(number_of_particles) ::  p_int                  !:
    200     REAL(wp), DIMENSION(number_of_particles) ::  thermal_conductivity_v !:
    201     REAL(wp), DIMENSION(number_of_particles) ::  t_int                  !:
    202     REAL(wp), DIMENSION(number_of_particles) ::  xv                     !:
    203     REAL(wp), DIMENSION(number_of_particles) ::  yv                     !:
    204     REAL(wp), DIMENSION(number_of_particles) ::  zv                     !:
     171    REAL(wp), PARAMETER ::  a21 = 2.0_wp               !<
     172    REAL(wp), PARAMETER ::  a31 = 48.0_wp / 25.0_wp    !<
     173    REAL(wp), PARAMETER ::  a32 = 6.0_wp / 25.0_wp     !<
     174    REAL(wp), PARAMETER ::  b1 = 19.0_wp / 9.0_wp      !<
     175    REAL(wp), PARAMETER ::  b2 = 0.5_wp                !<
     176    REAL(wp), PARAMETER ::  b3 = 25.0_wp / 108.0_wp    !<
     177    REAL(wp), PARAMETER ::  b4 = 125.0_wp / 108.0_wp   !<
     178    REAL(wp), PARAMETER ::  c21 = -8.0_wp              !<
     179    REAL(wp), PARAMETER ::  c31 = 372.0_wp / 25.0_wp   !<
     180    REAL(wp), PARAMETER ::  c32 = 12.0_wp / 5.0_wp     !<
     181    REAL(wp), PARAMETER ::  c41 = -112.0_wp / 125.0_wp !<
     182    REAL(wp), PARAMETER ::  c42 = -54.0_wp / 125.0_wp  !<
     183    REAL(wp), PARAMETER ::  c43 = -2.0_wp / 5.0_wp     !<
     184    REAL(wp), PARAMETER ::  errcon = 0.1296_wp         !<
     185    REAL(wp), PARAMETER ::  e1 = 17.0_wp / 54.0_wp     !<
     186    REAL(wp), PARAMETER ::  e2 = 7.0_wp / 36.0_wp      !<
     187    REAL(wp), PARAMETER ::  e3 = 0.0_wp                !<
     188    REAL(wp), PARAMETER ::  e4 = 125.0_wp / 108.0_wp   !<
     189    REAL(wp), PARAMETER ::  gam = 0.5_wp               !<
     190    REAL(wp), PARAMETER ::  grow = 1.5_wp              !<
     191    REAL(wp), PARAMETER ::  pgrow = -0.25_wp           !<
     192    REAL(wp), PARAMETER ::  pshrnk = -1.0_wp /3.0_wp   !<
     193    REAL(wp), PARAMETER ::  shrnk = 0.5_wp             !<
     194
     195    REAL(wp), DIMENSION(number_of_particles) ::  afactor_v              !<
     196    REAL(wp), DIMENSION(number_of_particles) ::  diff_coeff_v           !<
     197    REAL(wp), DIMENSION(number_of_particles) ::  e_s                    !<
     198    REAL(wp), DIMENSION(number_of_particles) ::  e_a                    !<
     199    REAL(wp), DIMENSION(number_of_particles) ::  new_r                  !<
     200    REAL(wp), DIMENSION(number_of_particles) ::  p_int                  !<
     201    REAL(wp), DIMENSION(number_of_particles) ::  thermal_conductivity_v !<
     202    REAL(wp), DIMENSION(number_of_particles) ::  t_int                  !<
     203    REAL(wp), DIMENSION(number_of_particles) ::  xv                     !<
     204    REAL(wp), DIMENSION(number_of_particles) ::  yv                     !<
     205    REAL(wp), DIMENSION(number_of_particles) ::  zv                     !<
    205206
    206207
Note: See TracChangeset for help on using the changeset viewer.