Ignore:
Timestamp:
Jun 8, 2017 2:59:01 PM (7 years ago)
Author:
schwenkel
Message:

Implemented splitting and merging algorithm

File:
1 edited

Legend:

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

    r2183 r2263  
    2525! -----------------
    2626! $Id$
     27! Implemented splitting and merging algorithm
     28!
     29! 2183 2017-03-17 14:29:15Z schwenkel
    2730!
    2831! 2182 2017-03-17 14:27:40Z schwenkel
     
    8689    CHARACTER(LEN=15) ::  collision_algorithm = 'all_or_nothing'  !< collision algorithm
    8790    CHARACTER(LEN=15) ::  collision_kernel = 'none'               !< collision kernel
    88 
    89     INTEGER(iwp) ::  deleted_particles = 0,                                    &
    90                      dissipation_classes = 10, ibc_par_lr,                     &
    91                      ibc_par_ns, ibc_par_b, ibc_par_t, iran_part = -1234567,   &
    92                      maximum_number_of_particles = 0,                          &
    93                      min_nr_particle = 50,                                     &
    94                      mpi_particle_type,                                        &
    95                      number_of_particles = 0,                                  &
    96                      number_of_particle_groups = 1,                            &
    97                      number_of_sublayers = 20,                                 &
    98                      number_particles_per_gridbox = -1,                        &
    99                      offset_ocean_nzt = 0,                                     &
    100                      offset_ocean_nzt_m1 = 0, particles_per_point = 1,         &
    101                      particle_file_count = 0, radius_classes = 20,             &
    102                      sort_count = 0, step_dealloc = 100,                       &
    103                      total_number_of_particles,                                &
    104                      trlp_count_sum, trlp_count_recv_sum, trrp_count_sum,      &
    105                      trrp_count_recv_sum, trsp_count_sum, trsp_count_recv_sum, &
    106                      trnp_count_sum, trnp_count_recv_sum
    107 
    108     INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10
    109 
    110     INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count
    111 
    112     LOGICAL ::  all_or_nothing = .FALSE., average_impact = .FALSE.,            &
    113                 curvature_solution_effects = .FALSE.,                          &
    114                 deallocate_memory = .TRUE.,                                    &
    115                 hall_kernel = .FALSE., particle_advection = .FALSE.,           &
    116                 random_start_position = .FALSE.,                               &
    117                 read_particles_from_restartfile = .TRUE.,                      &
    118                 seed_follows_topography = .FALSE.,                             &
    119                 uniform_particles = .TRUE., use_kernel_tables = .FALSE.,       &
    120                 use_sgs_for_particles = .FALSE., wang_kernel = .FALSE.,        &
    121                 write_particle_statistics = .FALSE.
    122 
     91    CHARACTER(LEN=5) ::  splitting_function = 'gamma'             !< function for calculation critical weighting factor
     92    CHARACTER(LEN=5) ::  splitting_mode = 'const'                 !< splitting mode
     93
     94
     95    INTEGER(iwp) ::  deleted_particles = 0                        !< number of deleted particles per time step
     96    INTEGER(iwp) ::  dissipation_classes = 10                     !< number of dissipation classes
     97    INTEGER(iwp) ::  ibc_par_b                                    !< particle bottom boundary condition dummy
     98    INTEGER(iwp) ::  ibc_par_lr                                   !< particle left/right boundary condition dummy
     99    INTEGER(iwp) ::  ibc_par_ns                                   !< particle north/south boundary condition dummy
     100    INTEGER(iwp) ::  ibc_par_t                                    !< particle top boundary condition dummy
     101    INTEGER(iwp) ::  iran_part = -1234567                         !< number for random generator
     102    INTEGER(iwp) ::  isf                                          !< dummy for splitting function
     103    INTEGER(iwp) ::  i_splitting_mode                             !< dummy for splitting mode
     104    INTEGER(iwp) ::  maximum_number_of_particles = 0              !< maximum number of particles on a PE (can be removed?)
     105    INTEGER(iwp) ::  max_number_particles_per_gridbox = 30        !< maximum number of particles per gridbox (used in splitting algorithm)
     106    INTEGER(iwp) ::  merge_drp = 0                                !< number of merged droplets
     107    INTEGER(iwp) ::  min_nr_particle = 50                         !< minimum number of particles for which memory is allocated at every grid cell         
     108    INTEGER(iwp) ::  mpi_particle_type                            !< parameter for particle PE particle exchange
     109    INTEGER(iwp) ::  new_particles = 0                            !< number of new particles
     110    INTEGER(iwp) ::  n_max = 100                                  !< number of radii bin for splitting functions     
     111    INTEGER(iwp) ::  number_of_particles = 0                      !< number of particles for each grid box (3d array is saved on prt_count)           
     112    INTEGER(iwp) ::  number_of_particle_groups = 1                !< number of particle groups to be used           
     113    INTEGER(iwp) ::  number_of_sublayers = 20                     !< number of sublayers for particle velocities betwenn surface and first grid level         
     114    INTEGER(iwp) ::  number_particles_per_gridbox = -1            !< number of particles which are created in every grid box           
     115    INTEGER(iwp) ::  offset_ocean_nzt = 0                         !< in case of oceans runs, the vertical index calculations need an offset         
     116    INTEGER(iwp) ::  offset_ocean_nzt_m1 = 0                      !< in case of oceans runs, the vertical index calculations need an offset
     117    INTEGER(iwp) ::  particles_per_point = 1                      !< number of particles to be started per point
     118    INTEGER(iwp) ::  particle_file_count = 0                      !< can be removed ?
     119    INTEGER(iwp) ::  radius_classes = 20                          !< number of radius classes to be used in the collision efficiency table
     120    INTEGER(iwp) ::  sort_count = 0                               !< counter for sorting particles
     121    INTEGER(iwp) ::  splitting_factor = 2                         !< splitting factor
     122    INTEGER(iwp) ::  splitting_factor_max = 5                     !< maximum splittig factor
     123    INTEGER(iwp) ::  step_dealloc = 100                           !< number of timesteps after which particle memory is deallocated
     124    INTEGER(iwp) ::  sum_merge_drp = 0                            !< sum of merged super droplets
     125    INTEGER(iwp) ::  sum_new_particles = 0                        !< sum of created particles (in splitting algorithm)
     126    INTEGER(iwp) ::  total_number_of_particles                    !< total number of particles in the whole model domain           
     127    INTEGER(iwp) ::  trlp_count_sum                               !< parameter for particle exchange of PEs
     128    INTEGER(iwp) ::  trlp_count_recv_sum                          !< parameter for particle exchange of PEs
     129    INTEGER(iwp) ::  trrp_count_sum                               !< parameter for particle exchange of PEs
     130    INTEGER(iwp) ::  trrp_count_recv_sum                          !< parameter for particle exchange of PEs
     131    INTEGER(iwp) ::  trsp_count_sum                               !< parameter for particle exchange of PEs
     132    INTEGER(iwp) ::  trsp_count_recv_sum                          !< parameter for particle exchange of PEs
     133    INTEGER(iwp) ::  trnp_count_sum                               !< parameter for particle exchange of PEs
     134    INTEGER(iwp) ::  trnp_count_recv_sum                          !< parameter for particle exchange of PEs
     135
     136    INTEGER(iwp), PARAMETER ::  max_number_of_particle_groups = 10 !< maximum allowed number of particle groups
     137
     138    INTEGER(iwp), DIMENSION(:,:,:), ALLOCATABLE ::  prt_count  !< 3d array of number of particles of every grid box
     139
     140    LOGICAL ::  all_or_nothing = .FALSE.                  !< flag for collision algorithm
     141    LOGICAL ::  average_impact = .FALSE.                  !< flag for collision algortihm
     142    LOGICAL ::  curvature_solution_effects = .FALSE.      !< parameter to consider solution and curvature effects on the equilibrium vapor pressure of cloud droplets                     
     143    LOGICAL ::  deallocate_memory = .TRUE.                !< parameter to enable deallocation of unused memory                   
     144    LOGICAL ::  hall_kernel = .FALSE.                     !< flag for collision kernel
     145    LOGICAL ::  init_aerosol_probabilistic = .FALSE.      !< parameter to steer the initialization of the aerosol spectrum
     146    LOGICAL ::  merging = .FALSE.                         !< parameter to enable merging of super droplets
     147    LOGICAL ::  monodisperse_aerosols = .FALSE.           !< parameter to steer the initialization of the aerosol spectrum
     148    LOGICAL ::  particle_advection = .FALSE.              !< parameter to steer the advection of particles
     149    LOGICAL ::  random_start_position = .FALSE.           !< parameter to initialize particles on random positon (within one grid box)                   
     150    LOGICAL ::  read_particles_from_restartfile = .TRUE.  !< read particle data from the previous run                   
     151    LOGICAL ::  seed_follows_topography = .FALSE.         !< heights of initial particles are interpreted relative to the given topography
     152    LOGICAL ::  splitting = .FALSE.                       !< parameter to enable the splitting of super droplets
     153    LOGICAL ::  uniform_particles = .TRUE.                !< can be removed?
     154    LOGICAL ::  use_kernel_tables = .FALSE.               !< parameter, which turns on the use of precalculated collision kernels
     155    LOGICAL ::  use_sgs_for_particles = .FALSE.           !< parameter to use sgs velocities for particles
     156    LOGICAL ::  wang_kernel = .FALSE.                     !< flag for collision kernel
     157    LOGICAL ::  write_particle_statistics = .FALSE.       !< switch on/off output of particle information (statistical information)
     158               
    123159    LOGICAL, DIMENSION(max_number_of_particle_groups) ::                       &
    124                 vertical_particle_advection = .TRUE.
    125 
    126     REAL(wp) ::  alloc_factor = 20.0_wp, c_0 = 3.0_wp,                         &
    127                  dt_min_part = 0.0002_wp, dt_prel = 9999999.9_wp,              &
    128                  dt_write_particle_data = 9999999.9_wp,                        &
    129                  end_time_prel = 9999999.9_wp,                                 &
    130                  initial_weighting_factor = 1.0_wp,                            &
    131                  number_concentration     = -1.0_wp,                           &
    132                  particle_advection_start = 0.0_wp,                            &
    133                  sgs_wf_part, time_prel = 0.0_wp, time_sort_particles = 0.0_wp,&
    134                  time_write_particle_data = 0.0_wp, z0_av_global
    135 
    136     REAL(wp), DIMENSION(max_number_of_particle_groups) ::                      &
    137                  density_ratio = 9999999.9_wp, pdx = 9999999.9_wp,             &
    138                  pdy = 9999999.9_wp, pdz = 9999999.9_wp, psb = 9999999.9_wp,   &
    139                  psl = 9999999.9_wp, psn = 9999999.9_wp, psr = 9999999.9_wp,   &
    140                  pss = 9999999.9_wp, pst = 9999999.9_wp, radius = 9999999.9_wp
    141 
    142     REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0
    143 
     160                vertical_particle_advection = .TRUE.              !< Switch on/off vertical particle transport
     161
     162    REAL(wp) ::  alloc_factor = 20.0_wp                           !< memory allocated additionally to the memory needed for initial particles at a given grid cell
     163    REAL(wp) ::  c_0 = 3.0_wp                                     !< parameter for lagrangian timescale
     164    REAL(wp) ::  dt_min_part = 0.0002_wp                          !< minimum particle time step when SGS velocities are used (s)
     165    REAL(wp) ::  dt_prel = 9999999.9_wp                           !< temporal interval at which particles are to be released from a particle source (in s)
     166    REAL(wp) ::  dt_write_particle_data = 9999999.9_wp            !< temporal interval for output of particle data (in s)             
     167    REAL(wp) ::  end_time_prel = 9999999.9_wp                     !< time of the last release of particles (in s).           
     168    REAL(wp) ::  initial_weighting_factor = 1.0_wp                !< weighting factor used for initialization
     169    REAL(wp) ::  molecular_weight_of_solute = 0.05844_wp          !< mol. m. NaCl (kg mol-1)
     170    REAL(wp) ::  molecular_weight_of_water = 0.01801528_wp        !< mol. m. H2O (kg mol-1)
     171    REAL(wp) ::  n1 = 100.0_wp                                    !< number concentration of the first log-normal distribution (dry aerosol initialization)
     172    REAL(wp) ::  n2 = 0.0_wp                                      !< see n1
     173    REAL(wp) ::  n3 = 0.0_wp                                      !< see n1
     174    REAL(wp) ::  number_concentration = -1.0_wp                   !< initial particle number concentration (in units of 1/cm^-3)
     175    REAL(wp) ::  particle_advection_start = 0.0_wp                !< time of the first release of particles (in s).
     176    REAL(wp) ::  radius_merge = 1.0E-7_wp                         !< particles with a smaller radius are merged if merging is set
     177    REAL(wp) ::  radius_split = 40.0E-6_wp                        !< particles with a bigger radius are splitted if splittig is set
     178    REAL(wp) ::  rho_s = 2165.0_wp                                !< density of NaCl (kg m-3)
     179    REAL(wp) ::  rm1 = 0.05E-6_wp                                 !< mode radius of the first log-normal distribution (dry aerosol initialization)
     180    REAL(wp) ::  rm2 = 0.05E-6_wp                                 !< see rm1
     181    REAL(wp) ::  rm3 = 0.05E-6_wp                                 !< see rm2
     182    REAL(wp) ::  s1 = 2.0_wp                                      !< geometric standard deviation of the first log-normal distribution (dry aerosol initialization)
     183    REAL(wp) ::  s2 = 2.0_wp                                      !< see s1
     184    REAL(wp) ::  s3 = 2.0_wp                                      !< see s1
     185    REAL(wp) ::  sgs_wf_part                                      !< parameter for sgs
     186    REAL(wp) ::  time_prel = 0.0_wp                               !< time for particle release
     187    REAL(wp) ::  time_sort_particles = 0.0_wp                     !< can be removed?
     188    REAL(wp) ::  time_write_particle_data = 0.0_wp                !< write particle data at current time on file
     189    REAL(wp) ::  vanthoff = 2.0_wp                                !< van't Hoff factor for NaCl
     190    REAL(wp) ::  weight_factor_merge = -1.0_wp                    !< critical weighting factor for merging
     191    REAL(wp) ::  weight_factor_split = -1.0_wp                    !< critical weighting factor for splitting
     192    REAL(wp) ::  z0_av_global                                     !< horizontal mean value of z0
     193
     194    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  density_ratio = 9999999.9_wp  !< ratio of the density of the fluid and the density of the particles   
     195    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdx = 9999999.9_wp            !< distance along x between particles within a particle source (in m)
     196    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdy = 9999999.9_wp            !< distance along y between particles within a particle source (in m)
     197    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pdz = 9999999.9_wp            !< distance along z between particles within a particle source (in m)
     198    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psb = 9999999.9_wp            !< bottom edge of a particle source (in m)
     199    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psl = 9999999.9_wp            !< left edge of a particle source (in m)
     200    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psn = 9999999.9_wp            !< rear ("north") edge of a particle source (in m)
     201    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  psr = 9999999.9_wp            !< right edge of a particle source (in m).
     202    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pss = 9999999.9_wp            !< front ("south") edge of a particle source (in m).
     203    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  pst = 9999999.9_wp            !< top edge of a particle source (in m).
     204    REAL(wp), DIMENSION(max_number_of_particle_groups) ::  radius = 9999999.9_wp         !< particle radius (in m).
     205
     206    REAL(wp), DIMENSION(:), ALLOCATABLE     ::  log_z_z0   !< Precalculate LOG(z/z0)
     207
     208   
    144209    TYPE particle_type
    145210        SEQUENCE
     
    181246    TYPE(block_offset_def), DIMENSION(0:7)         ::  block_offset
    182247
    183 !
    184 !-- Lagrangian cloud model constants (especially for steering aerosols)
    185     REAL(wp) ::  molecular_weight_of_solute = 0.05844_wp    !< mol. m. NaCl (kg mol-1)
    186     REAL(wp) ::  molecular_weight_of_water = 0.01801528_wp  !< mol. m. H2O (kg mol-1)
    187     REAL(wp) ::  rho_s = 2165.0_wp                          !< density of NaCl (kg m-3)
    188     REAL(wp) ::  vanthoff = 2.0_wp                          !< van't Hoff factor for NaCl
    189 
    190     REAL(wp) ::  n1 = 100.0_wp, s1 = 2.0_wp, rm1 = 0.05E-6_wp, &
    191                  n2 =   0.0_wp, s2 = 2.0_wp, rm2 = 0.05E-6_wp, &
    192                  n3 =   0.0_wp, s3 = 2.0_wp, rm3 = 0.05E-6_wp
    193 
    194     LOGICAL  ::  monodisperse_aerosols      = .FALSE.       !< initialize monodisperse aerosols
    195     LOGICAL  ::  init_aerosol_probabilistic = .FALSE.       !< how to initialize aerosol spectra
    196 
    197248    SAVE
    198249
Note: See TracChangeset for help on using the changeset viewer.