Ignore:
Timestamp:
Jul 14, 2017 8:26:51 PM (7 years ago)
Author:
hoffmann
Message:

various improvements of the LCM

File:
1 edited

Legend:

Unmodified
Added
Removed
  • palm/trunk/SOURCE/mod_particle_attributes.f90

    r2305 r2312  
    2020! Current revisions:
    2121! ------------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! Aerosol initialization improved.
     28!
     29! 2305 2017-07-06 11:18:47Z hoffmann
    2730! Improved calculation of particle IDs.
    28 ! 
     31!
    2932! 2278 2017-06-12 13:08:18Z schwenkel
    3033! Added comments
    31 ! 
     34!
    3235! 2265 2017-06-08 16:58:28Z schwenkel
    3336! Unused variables removed.
    34 ! 
     37!
    3538! 2263 2017-06-08 14:59:01Z schwenkel
    3639! Implemented splitting and merging algorithm
    37 ! 
     40!
    3841! 2183 2017-03-17 14:29:15Z schwenkel
    3942!
    4043! 2182 2017-03-17 14:27:40Z schwenkel
    4144! Added parameters for simplified particle initialization.
    42 ! 
     45!
    4346! 2122 2017-01-18 12:22:54Z hoffmann
    4447! Calculation of particle ID
     
    4851! 2000 2016-08-20 18:09:15Z knoop
    4952! Forced header and separation lines into 80 columns
    50 ! 
     53!
    5154! 1936 2016-06-13 13:37:44Z suehring
    5255! +deallocate_memory, step_dealloc
     
    7174!
    7275! 1727 2015-11-20 07:22:02Z knoop
    73 ! Bugfix: Cause of syntax warning gfortran preprocessor removed 
    74 ! 
     76! Bugfix: Cause of syntax warning gfortran preprocessor removed
     77!
    7578! 1682 2015-10-07 23:56:08Z knoop
    76 ! Code annotations made doxygen readable 
     79! Code annotations made doxygen readable
    7780!
    7881! 1575 2015-03-27 09:56:27Z raasch
     
    8891!------------------------------------------------------------------------------!
    8992MODULE particle_attributes
    90  
     93
    9194
    9295    USE kinds
    9396
    94     CHARACTER(LEN=15) ::  bc_par_lr = 'cyclic'                    !< left/right boundary condition
    95     CHARACTER(LEN=15) ::  bc_par_ns = 'cyclic'                    !< north/south boundary condition
    96     CHARACTER(LEN=15) ::  bc_par_b  = 'reflect'                   !< bottom boundary condition
    97     CHARACTER(LEN=15) ::  bc_par_t  = 'absorb'                    !< top boundary condition
    98     CHARACTER(LEN=15) ::  collision_algorithm = 'all_or_nothing'  !< collision algorithm
    99     CHARACTER(LEN=15) ::  collision_kernel = 'none'               !< collision kernel
    100     CHARACTER(LEN=5) ::  splitting_function = 'gamma'             !< function for calculation critical weighting factor
    101     CHARACTER(LEN=5) ::  splitting_mode = 'const'                 !< splitting mode
    102 
    103 
    104     INTEGER(iwp) ::  deleted_particles = 0                        !< number of deleted particles per time step
     97    CHARACTER(LEN=15) ::  aero_type = 'maritime'                   !< aerosol type
     98    CHARACTER(LEN=15) ::  bc_par_lr = 'cyclic'                     !< left/right boundary condition
     99    CHARACTER(LEN=15) ::  bc_par_ns = 'cyclic'                     !< north/south boundary condition
     100    CHARACTER(LEN=15) ::  bc_par_b  = 'reflect'                    !< bottom boundary condition
     101    CHARACTER(LEN=15) ::  bc_par_t  = 'absorb'                     !< top boundary condition
     102    CHARACTER(LEN=15) ::  collision_kernel = 'none'                !< collision kernel
     103    CHARACTER(LEN=5)  ::  splitting_function = 'gamma'             !< function for calculation critical weighting factor
     104    CHARACTER(LEN=5)  ::  splitting_mode = 'const'                 !< splitting mode
     105
     106    INTEGER(iwp) ::  deleted_particles = 0                        !< number of deleted particles per time step
    105107    INTEGER(iwp) ::  dissipation_classes = 10                     !< namelist parameter (see documentation)
    106108    INTEGER(iwp) ::  ibc_par_b                                    !< particle bottom boundary condition dummy
     
    113115    INTEGER(iwp) ::  max_number_particles_per_gridbox = 100       !< namelist parameter (see documentation)
    114116    INTEGER(iwp) ::  merge_drp = 0                                !< number of merged droplets
    115     INTEGER(iwp) ::  min_nr_particle = 50                         !< namelist parameter (see documentation)         
     117    INTEGER(iwp) ::  min_nr_particle = 50                         !< namelist parameter (see documentation)
    116118    INTEGER(iwp) ::  new_particles = 0                            !< number of new particles
    117     INTEGER(iwp) ::  n_max = 100                                  !< number of radii bin for splitting functions     
    118     INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)           
    119     INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)           
    120     INTEGER(iwp) ::  number_of_sublayers = 20                     !< number of sublayers for particle velocities betwenn surface and first grid level         
    121     INTEGER(iwp) ::  number_particles_per_gridbox = -1            !< namelist parameter (see documentation)         
    122     INTEGER(iwp) ::  offset_ocean_nzt = 0                         !< in case of oceans runs, the vertical index calculations need an offset         
     119    INTEGER(iwp) ::  n_max = 100                                  !< number of radii bin for splitting functions
     120    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)
     121    INTEGER(iwp) ::  number_of_particle_groups = 1                !< namelist parameter (see documentation)
     122    INTEGER(iwp) ::  number_of_sublayers = 20                     !< number of sublayers for particle velocities betwenn surface and first grid level
     123    INTEGER(iwp) ::  number_particles_per_gridbox = -1            !< namelist parameter (see documentation)
     124    INTEGER(iwp) ::  offset_ocean_nzt = 0                         !< in case of oceans runs, the vertical index calculations need an offset
    123125    INTEGER(iwp) ::  offset_ocean_nzt_m1 = 0                      !< in case of oceans runs, the vertical index calculations need an offset
    124126    INTEGER(iwp) ::  particles_per_point = 1                      !< namelist parameter (see documentation)
     
    130132    INTEGER(iwp) ::  sum_merge_drp = 0                            !< sum of merged super droplets
    131133    INTEGER(iwp) ::  sum_new_particles = 0                        !< sum of created particles (in splitting algorithm)
    132     INTEGER(iwp) ::  total_number_of_particles                    !< total number of particles in the whole model domain           
     134    INTEGER(iwp) ::  total_number_of_particles                    !< total number of particles in the whole model domain
    133135    INTEGER(iwp) ::  trlp_count_sum                               !< parameter for particle exchange of PEs
    134136    INTEGER(iwp) ::  trlp_count_recv_sum                          !< parameter for particle exchange of PEs
     
    144146    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
    145147
    146     LOGICAL ::  all_or_nothing = .FALSE.                  !< flag for collision algorithm
    147     LOGICAL ::  average_impact = .FALSE.                  !< flag for collision algortihm
    148     LOGICAL ::  curvature_solution_effects = .FALSE.      !< namelist parameter (see documentation)                     
    149     LOGICAL ::  deallocate_memory = .TRUE.                !< namelist parameter (see documentation)                 
     148    LOGICAL ::  curvature_solution_effects = .FALSE.      !< namelist parameter (see documentation)
     149    LOGICAL ::  deallocate_memory = .TRUE.                !< namelist parameter (see documentation)
    150150    LOGICAL ::  hall_kernel = .FALSE.                     !< flag for collision kernel
    151     LOGICAL ::  init_aerosol_probabilistic = .FALSE.      !< namelist parameter (see documentation)
    152151    LOGICAL ::  merging = .FALSE.                         !< namelist parameter (see documentation)
    153     LOGICAL ::  monodisperse_aerosols = .FALSE.           !< namelist parameter (see documentation)
    154152    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
    155     LOGICAL ::  random_start_position = .FALSE.           !< namelist parameter (see documentation)                   
    156     LOGICAL ::  read_particles_from_restartfile = .TRUE.  !< namelist parameter (see documentation)                   
     153    LOGICAL ::  random_start_position = .FALSE.           !< namelist parameter (see documentation)
     154    LOGICAL ::  read_particles_from_restartfile = .TRUE.  !< namelist parameter (see documentation)
    157155    LOGICAL ::  seed_follows_topography = .FALSE.         !< namelist parameter (see documentation)
    158156    LOGICAL ::  splitting = .FALSE.                       !< namelist parameter (see documentation)
    159157    LOGICAL ::  use_kernel_tables = .FALSE.               !< parameter, which turns on the use of precalculated collision kernels
    160     LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation) 
     158    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< namelist parameter (see documentation)
    161159    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
    162160    LOGICAL ::  write_particle_statistics = .FALSE.       !< namelist parameter (see documentation)
    163                
     161
    164162    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
    165163                vertical_particle_advection = .TRUE.              !< Switch on/off vertical particle transport
    166164
     165    REAL(wp) ::  aero_weight = 1.0_wp                      !< namelist parameter (see documentation)
    167166    REAL(wp) ::  alloc_factor = 20.0_wp                    !< namelist parameter (see documentation)
    168167    REAL(wp) ::  c_0 = 3.0_wp                              !< parameter for lagrangian timescale
    169168    REAL(wp) ::  dt_min_part = 0.0002_wp                   !< minimum particle time step when SGS velocities are used (s)
    170169    REAL(wp) ::  dt_prel = 9999999.9_wp                    !< namelist parameter (see documentation)
    171     REAL(wp) ::  dt_write_particle_data = 9999999.9_wp     !< namelist parameter (see documentation)           
    172     REAL(wp) ::  end_time_prel = 9999999.9_wp              !< namelist parameter (see documentation)         
     170    REAL(wp) ::  dt_write_particle_data = 9999999.9_wp     !< namelist parameter (see documentation)
     171    REAL(wp) ::  end_time_prel = 9999999.9_wp              !< namelist parameter (see documentation)
    173172    REAL(wp) ::  initial_weighting_factor = 1.0_wp         !< namelist parameter (see documentation)
     173    REAL(wp) ::  log_sigma(3) = 1.0_wp                     !< namelist parameter (see documentation)
    174174    REAL(wp) ::  molecular_weight_of_solute = 0.05844_wp   !< mol. m. NaCl (kg mol-1)
    175175    REAL(wp) ::  molecular_weight_of_water = 0.01801528_wp !< mol. m. H2O (kg mol-1)
    176     REAL(wp) ::  n1 = 100.0_wp                             !< namelist parameter (see documentation)
    177     REAL(wp) ::  n2 = 0.0_wp                               !< namelist parameter (see documentation)
    178     REAL(wp) ::  n3 = 0.0_wp                               !< namelist parameter (see documentation)
     176    REAL(wp) ::  na(3) = 0.0_wp                            !< namelist parameter (see documentation)
    179177    REAL(wp) ::  number_concentration = -1.0_wp            !< namelist parameter (see documentation)
    180178    REAL(wp) ::  particle_advection_start = 0.0_wp         !< namelist parameter (see documentation)
    181179    REAL(wp) ::  radius_merge = 1.0E-7_wp                  !< namelist parameter (see documentation)
    182180    REAL(wp) ::  radius_split = 40.0E-6_wp                 !< namelist parameter (see documentation)
    183     REAL(wp) ::  rho_s = 2165.0_wp                         !< density of NaCl (kg m-3)
    184     REAL(wp) ::  rm1 = 0.05E-6_wp                          !< namelist parameter (see documentation)
    185     REAL(wp) ::  rm2 = 0.05E-6_wp                          !< namelist parameter (see documentation)
    186     REAL(wp) ::  rm3 = 0.05E-6_wp                          !< namelist parameter (see documentation)
    187     REAL(wp) ::  s1 = 2.0_wp                               !< namelist parameter (see documentation)
    188     REAL(wp) ::  s2 = 2.0_wp                               !< namelist parameter (see documentation)
    189     REAL(wp) ::  s3 = 2.0_wp                               !< namelist parameter (see documentation)
    190     REAL(wp) ::  sgs_wf_part                               !< parameter for sgs
     181    REAL(wp) ::  rho_s = 2165.0_wp                         !< density of NaCl (kg m-3)
     182    REAL(wp) ::  rm(3) = 1.0E-6_wp                         !< namelist parameter (see documentation)
     183    REAL(wp) ::  sgs_wf_part                               !< parameter for sgs
    191184    REAL(wp) ::  time_prel = 0.0_wp                        !< time for particle release
    192185    REAL(wp) ::  time_write_particle_data = 0.0_wp         !< write particle data at current time on file
     
    210203    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0   !< Precalculate LOG(z/z0)
    211204
    212    
     205
    213206    TYPE particle_type
     207        REAL(wp)     ::  aux1          !< auxiliary multi-purpose feature
     208        REAL(wp)     ::  aux2          !< auxiliary multi-purpose feature
    214209        REAL(wp)     ::  radius        !< radius of particle
    215210        REAL(wp)     ::  age           !< age of particle
    216         REAL(wp)     ::  age_m         !< 
     211        REAL(wp)     ::  age_m         !<
    217212        REAL(wp)     ::  dt_sum        !<
    218         REAL(wp)     ::  user          !< varible for user
    219         REAL(wp)     ::  e_m           !< interpolated sgs tke     
     213        REAL(wp)     ::  e_m           !< interpolated sgs tke
    220214        REAL(wp)     ::  origin_x      !< origin x-position of particle (changed cyclic bc)
    221215        REAL(wp)     ::  origin_y      !< origin y-position of particle (changed cyclic bc)
    222216        REAL(wp)     ::  origin_z      !< origin z-position of particle (changed cyclic bc)
    223         REAL(wp)     ::  rvar1         !< 
     217        REAL(wp)     ::  rvar1         !<
    224218        REAL(wp)     ::  rvar2         !<
    225         REAL(wp)     ::  rvar3         !< 
     219        REAL(wp)     ::  rvar3         !<
    226220        REAL(wp)     ::  speed_x       !< speed of particle in x
    227221        REAL(wp)     ::  speed_y       !< speed of particle in y
    228222        REAL(wp)     ::  speed_z       !< speed of particle in z
    229         REAL(wp)     ::  weight_factor !< weighting factor 
    230         REAL(wp)     ::  x             !< x-position 
    231         REAL(wp)     ::  y             !< y-position 
    232         REAL(wp)     ::  z             !< z-position 
     223        REAL(wp)     ::  weight_factor !< weighting factor
     224        REAL(wp)     ::  x             !< x-position
     225        REAL(wp)     ::  y             !< y-position
     226        REAL(wp)     ::  z             !< z-position
    233227        INTEGER(iwp) ::  class         !< radius class needed for collision
    234228        INTEGER(iwp) ::  group         !< number of particle group
     
    274268
    275269END MODULE particle_attributes
    276 
Note: See TracChangeset for help on using the changeset viewer.