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

    r1584 r1682  
    1  SUBROUTINE lpm_advec (ip,jp,kp)
    2 
     1!> @file lpm_advec.f90
    32!--------------------------------------------------------------------------------!
    43! This file is part of PALM.
     
    2019! Current revisions:
    2120! ------------------
    22 !
     21! Code annotations made doxygen readable
    2322!
    2423! Former revisions:
     
    6160! Description:
    6261! ------------
    63 ! Calculation of new particle positions due to advection using a simple Euler
    64 ! scheme. Particles may feel inertia effects. SGS transport can be included
    65 ! using the stochastic model of Weil et al. (2004, JAS, 61, 2877-2887).
     62!> Calculation of new particle positions due to advection using a simple Euler
     63!> scheme. Particles may feel inertia effects. SGS transport can be included
     64!> using the stochastic model of Weil et al. (2004, JAS, 61, 2877-2887).
    6665!------------------------------------------------------------------------------!
     66 SUBROUTINE lpm_advec (ip,jp,kp)
     67 
    6768
    6869    USE arrays_3d,                                                             &
     
    99100    IMPLICIT NONE
    100101
    101     INTEGER(iwp) ::  agp                         !:
    102     INTEGER(iwp) ::  gp_outside_of_building(1:8) !:
    103     INTEGER(iwp) ::  i                           !:
    104     INTEGER(iwp) ::  ip                          !:
    105     INTEGER(iwp) ::  j                           !:
    106     INTEGER(iwp) ::  jp                          !:
    107     INTEGER(iwp) ::  k                           !:
    108     INTEGER(iwp) ::  kp                          !:
    109     INTEGER(iwp) ::  kw                          !:
    110     INTEGER(iwp) ::  n                           !:
    111     INTEGER(iwp) ::  nb                          !:
    112     INTEGER(iwp) ::  num_gp                      !:
    113 
    114     INTEGER(iwp), DIMENSION(0:7) ::  start_index !:
    115     INTEGER(iwp), DIMENSION(0:7) ::  end_index   !:
    116 
    117     REAL(wp) ::  aa                 !:
    118     REAL(wp) ::  bb                 !:
    119     REAL(wp) ::  cc                 !:
    120     REAL(wp) ::  d_sum              !:
    121     REAL(wp) ::  d_z_p_z0           !:
    122     REAL(wp) ::  dd                 !:
    123     REAL(wp) ::  de_dx_int_l        !:
    124     REAL(wp) ::  de_dx_int_u        !:
    125     REAL(wp) ::  de_dy_int_l        !:
    126     REAL(wp) ::  de_dy_int_u        !:
    127     REAL(wp) ::  de_dt              !:
    128     REAL(wp) ::  de_dt_min          !:
    129     REAL(wp) ::  de_dz_int_l        !:
    130     REAL(wp) ::  de_dz_int_u        !:
    131     REAL(wp) ::  diss_int_l         !:
    132     REAL(wp) ::  diss_int_u         !:
    133     REAL(wp) ::  dt_gap             !:
    134     REAL(wp) ::  dt_particle_m      !:
    135     REAL(wp) ::  e_int_l            !:
    136     REAL(wp) ::  e_int_u            !:
    137     REAL(wp) ::  e_mean_int         !:
    138     REAL(wp) ::  exp_arg            !:
    139     REAL(wp) ::  exp_term           !:
    140     REAL(wp) ::  gg                 !:
    141     REAL(wp) ::  height_int         !:
    142     REAL(wp) ::  height_p           !:
    143     REAL(wp) ::  lagr_timescale     !:
    144     REAL(wp) ::  location(1:30,1:3) !:
    145     REAL(wp) ::  random_gauss       !:
    146     REAL(wp) ::  u_int_l            !:
    147     REAL(wp) ::  u_int_u            !:
    148     REAL(wp) ::  us_int             !:
    149     REAL(wp) ::  v_int_l            !:
    150     REAL(wp) ::  v_int_u            !:
    151     REAL(wp) ::  vv_int             !:
    152     REAL(wp) ::  w_int_l            !:
    153     REAL(wp) ::  w_int_u            !:
    154     REAL(wp) ::  x                  !:
    155     REAL(wp) ::  y                  !:
    156     REAL(wp) ::  z_p                !:   
    157 
    158     REAL(wp), DIMENSION(1:30) ::  d_gp_pl !:
    159     REAL(wp), DIMENSION(1:30) ::  de_dxi  !:
    160     REAL(wp), DIMENSION(1:30) ::  de_dyi  !:
    161     REAL(wp), DIMENSION(1:30) ::  de_dzi  !:
    162     REAL(wp), DIMENSION(1:30) ::  dissi   !:
    163     REAL(wp), DIMENSION(1:30) ::  ei      !:
    164 
    165     REAL(wp), DIMENSION(number_of_particles) ::  dens_ratio   !:
    166     REAL(wp), DIMENSION(number_of_particles) ::  de_dx_int    !:
    167     REAL(wp), DIMENSION(number_of_particles) ::  de_dy_int    !:
    168     REAL(wp), DIMENSION(number_of_particles) ::  de_dz_int    !:
    169     REAL(wp), DIMENSION(number_of_particles) ::  diss_int     !:
    170     REAL(wp), DIMENSION(number_of_particles) ::  dt_particle  !:
    171     REAL(wp), DIMENSION(number_of_particles) ::  e_int        !:
    172     REAL(wp), DIMENSION(number_of_particles) ::  fs_int       !:
    173     REAL(wp), DIMENSION(number_of_particles) ::  log_z_z0_int !:
    174     REAL(wp), DIMENSION(number_of_particles) ::  u_int        !:
    175     REAL(wp), DIMENSION(number_of_particles) ::  v_int        !:
    176     REAL(wp), DIMENSION(number_of_particles) ::  w_int        !:
    177     REAL(wp), DIMENSION(number_of_particles) ::  xv           !:
    178     REAL(wp), DIMENSION(number_of_particles) ::  yv           !:
    179     REAL(wp), DIMENSION(number_of_particles) ::  zv           !:
    180 
    181     REAL(wp), DIMENSION(number_of_particles, 3) ::  rg !:
     102    INTEGER(iwp) ::  agp                         !<
     103    INTEGER(iwp) ::  gp_outside_of_building(1:8) !<
     104    INTEGER(iwp) ::  i                           !<
     105    INTEGER(iwp) ::  ip                          !<
     106    INTEGER(iwp) ::  j                           !<
     107    INTEGER(iwp) ::  jp                          !<
     108    INTEGER(iwp) ::  k                           !<
     109    INTEGER(iwp) ::  kp                          !<
     110    INTEGER(iwp) ::  kw                          !<
     111    INTEGER(iwp) ::  n                           !<
     112    INTEGER(iwp) ::  nb                          !<
     113    INTEGER(iwp) ::  num_gp                      !<
     114
     115    INTEGER(iwp), DIMENSION(0:7) ::  start_index !<
     116    INTEGER(iwp), DIMENSION(0:7) ::  end_index   !<
     117
     118    REAL(wp) ::  aa                 !<
     119    REAL(wp) ::  bb                 !<
     120    REAL(wp) ::  cc                 !<
     121    REAL(wp) ::  d_sum              !<
     122    REAL(wp) ::  d_z_p_z0           !<
     123    REAL(wp) ::  dd                 !<
     124    REAL(wp) ::  de_dx_int_l        !<
     125    REAL(wp) ::  de_dx_int_u        !<
     126    REAL(wp) ::  de_dy_int_l        !<
     127    REAL(wp) ::  de_dy_int_u        !<
     128    REAL(wp) ::  de_dt              !<
     129    REAL(wp) ::  de_dt_min          !<
     130    REAL(wp) ::  de_dz_int_l        !<
     131    REAL(wp) ::  de_dz_int_u        !<
     132    REAL(wp) ::  diss_int_l         !<
     133    REAL(wp) ::  diss_int_u         !<
     134    REAL(wp) ::  dt_gap             !<
     135    REAL(wp) ::  dt_particle_m      !<
     136    REAL(wp) ::  e_int_l            !<
     137    REAL(wp) ::  e_int_u            !<
     138    REAL(wp) ::  e_mean_int         !<
     139    REAL(wp) ::  exp_arg            !<
     140    REAL(wp) ::  exp_term           !<
     141    REAL(wp) ::  gg                 !<
     142    REAL(wp) ::  height_int         !<
     143    REAL(wp) ::  height_p           !<
     144    REAL(wp) ::  lagr_timescale     !<
     145    REAL(wp) ::  location(1:30,1:3) !<
     146    REAL(wp) ::  random_gauss       !<
     147    REAL(wp) ::  u_int_l            !<
     148    REAL(wp) ::  u_int_u            !<
     149    REAL(wp) ::  us_int             !<
     150    REAL(wp) ::  v_int_l            !<
     151    REAL(wp) ::  v_int_u            !<
     152    REAL(wp) ::  vv_int             !<
     153    REAL(wp) ::  w_int_l            !<
     154    REAL(wp) ::  w_int_u            !<
     155    REAL(wp) ::  x                  !<
     156    REAL(wp) ::  y                  !<
     157    REAL(wp) ::  z_p                !<   
     158
     159    REAL(wp), DIMENSION(1:30) ::  d_gp_pl !<
     160    REAL(wp), DIMENSION(1:30) ::  de_dxi  !<
     161    REAL(wp), DIMENSION(1:30) ::  de_dyi  !<
     162    REAL(wp), DIMENSION(1:30) ::  de_dzi  !<
     163    REAL(wp), DIMENSION(1:30) ::  dissi   !<
     164    REAL(wp), DIMENSION(1:30) ::  ei      !<
     165
     166    REAL(wp), DIMENSION(number_of_particles) ::  dens_ratio   !<
     167    REAL(wp), DIMENSION(number_of_particles) ::  de_dx_int    !<
     168    REAL(wp), DIMENSION(number_of_particles) ::  de_dy_int    !<
     169    REAL(wp), DIMENSION(number_of_particles) ::  de_dz_int    !<
     170    REAL(wp), DIMENSION(number_of_particles) ::  diss_int     !<
     171    REAL(wp), DIMENSION(number_of_particles) ::  dt_particle  !<
     172    REAL(wp), DIMENSION(number_of_particles) ::  e_int        !<
     173    REAL(wp), DIMENSION(number_of_particles) ::  fs_int       !<
     174    REAL(wp), DIMENSION(number_of_particles) ::  log_z_z0_int !<
     175    REAL(wp), DIMENSION(number_of_particles) ::  u_int        !<
     176    REAL(wp), DIMENSION(number_of_particles) ::  v_int        !<
     177    REAL(wp), DIMENSION(number_of_particles) ::  w_int        !<
     178    REAL(wp), DIMENSION(number_of_particles) ::  xv           !<
     179    REAL(wp), DIMENSION(number_of_particles) ::  yv           !<
     180    REAL(wp), DIMENSION(number_of_particles) ::  zv           !<
     181
     182    REAL(wp), DIMENSION(number_of_particles, 3) ::  rg !<
    182183
    183184    CALL cpu_log( log_point_s(44), 'lpm_advec', 'continue' )
Note: See TracChangeset for help on using the changeset viewer.