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/package_parin.f90

    r2263 r2312  
    2020! Current revisions:
    2121! -----------------
    22 ! 
    23 ! 
     22!
     23!
    2424! Former revisions:
    2525! -----------------
    2626! $Id$
     27! Aerosol initialization improved.
     28!
     29! 2263 2017-06-08 14:59:01Z schwenkel
    2730! Implemented splitting and merging algorithm
    28 ! 
     31!
    2932! 2183 2017-03-17 14:29:15Z schwenkel
    3033!
    3134! 2182 2017-03-17 14:27:40Z schwenkel
    3235! Added parameters for simplified particle initialization.
    33 ! 
     36!
    3437! 2000 2016-08-20 18:09:15Z knoop
    3538! Forced header and separation lines into 80 columns
    36 ! 
     39!
    3740! 1936 2016-06-13 13:37:44Z suehring
    3841! +deallocate_memory, step_dealloc
    39 ! 
     42!
    4043! 1871 2016-04-15 11:46:09Z hoffmann
    4144! Initialization of aerosols added.
    42 ! 
     45!
    4346! 1833 2016-04-07 14:23:03Z raasch
    4447! reading of spectra_par moved to spectra_mod
    45 ! 
     48!
    4649! 1831 2016-04-07 13:15:51Z hoffmann
    4750! curvature_solution_effects added
     
    5053! Reading of &radiation_par moved to radiation_model_mod.
    5154! Reading of &canopy_par moved to plant_canopy_model_mod.
    52 ! 
     55!
    5356! 822 2016-04-07 07:49:42Z hoffmann
    5457! +collision_algorithm
     
    5760! 1817 2016-04-06 15:44:20Z maronga
    5861! Reading of &lsm_par moved to land_surface_model_mod.
    59 ! 
     62!
    6063! 1788 2016-03-10 11:01:04Z maronga
    6164! Parameter dewfall removed.
     
    6669! 1757 2016-02-22 15:49:32Z maronga
    6770! Added parameter unscheduled_radiation_calls
    68 ! 
     71!
    6972! 1691 2015-10-26 16:17:44Z maronga
    7073! Added skip_time_do_lsm, skip_time_do_radiation, and emissivity
    71 ! 
     74!
    7275! 1682 2015-10-07 23:56:08Z knoop
    73 ! Code annotations made doxygen readable 
    74 ! 
     76! Code annotations made doxygen readable
     77!
    7578! 1585 2015-04-30 07:05:52Z maronga
    7679! Added several radiation_par parameters
     
    8184! 1553 2015-03-03 17:33:54Z maronga
    8285! Resorting of lsm_par
    83 ! 
     86!
    8487! 1551 2015-03-03 14:18:16Z maronga
    8588! Several changes in the liste for land surface model and radiation model
    86 ! 
     89!
    8790! 1496 2014-12-02 17:25:50Z maronga
    8891! Added support for the land surface model and radiation scheme
    89 ! 
     92!
    9093! 1484 2014-10-21 10:53:05Z kanani
    9194! Changes due to new module structure of the plant canopy model:
    9295!   module plant_canopy_model_mod added,
    93 !   new package/namelist canopy_par added, i.e. the canopy model is no longer 
     96!   new package/namelist canopy_par added, i.e. the canopy model is no longer
    9497!   steered over the inipar-namelist,
    9598!   drag_coefficient, leaf_surface_concentration and scalar_exchange_coefficient
    9699!   renamed to canopy_drag_coeff, leaf_surface_conc and leaf_scalar_exch_coeff.
    97100! Changed statement tags in CONTINUE-statement
    98 ! 
     101!
    99102! 1367 2014-04-23 15:18:30Z witha
    100103! Bugfix: module kinds must be used
     
    103106! +alloc_factor, + min_nr_particle
    104107! -dt_sort_particles, -maximum_number_of_particles
    105 ! 
     108!
    106109! 1340 2014-03-25 19:45:13Z kanani
    107110! REAL constants defined as wp-kinds
     
    138141!> software packages which are used optionally in the run.
    139142!>
    140 !> @todo Perform all actions in the respective submodules and remove 
     143!> @todo Perform all actions in the respective submodules and remove
    141144!>       package_parin
    142145!------------------------------------------------------------------------------!
    143146 SUBROUTINE package_parin
    144  
     147
    145148
    146149    USE control_parameters,                                                    &
     
    165168
    166169    USE particle_attributes,                                                   &
    167         ONLY:  alloc_factor, bc_par_b, bc_par_lr, bc_par_ns, bc_par_t,         &
    168                collision_algorithm, collision_kernel,                          &
     170        ONLY:  aero_type, aero_weight, alloc_factor, bc_par_b, bc_par_lr,      &
     171               bc_par_ns, bc_par_t, collision_kernel,                          &
    169172               curvature_solution_effects, deallocate_memory, density_ratio,   &
    170173               dissipation_classes, dt_min_part, dt_prel,                      &
    171174               dt_write_particle_data, end_time_prel, initial_weighting_factor,&
    172                init_aerosol_probabilistic, max_number_particles_per_gridbox,   &
    173                merging, min_nr_particle, monodisperse_aerosols, n1, n2, n3,    &
     175               log_sigma, max_number_particles_per_gridbox,                    &
     176               merging, min_nr_particle, na,                                   &
    174177               number_concentration, number_of_particle_groups,                &
    175178               number_particles_per_gridbox, particles_per_point,              &
     
    177180               psb, psl, psn, psr, pss, pst, radius, radius_classes,           &
    178181               radius_merge, radius_split, random_start_position,              &
    179                read_particles_from_restartfile, rm1, rm2, rm3,                 &
    180                seed_follows_topography, splitting, splitting_factor,           & 
     182               read_particles_from_restartfile, rm,                            &
     183               seed_follows_topography, splitting, splitting_factor,           &
    181184               splitting_factor_max, splitting_function, splitting_mode,       &
    182                step_dealloc, s1, s2, s3, use_sgs_for_particles,                &
     185               step_dealloc, use_sgs_for_particles,                            &
    183186               vertical_particle_advection, weight_factor_merge,               &
    184                weight_factor_split, write_particle_statistics               
     187               weight_factor_split, write_particle_statistics
    185188
    186189    IMPLICIT NONE
     
    206209                                  vc_size_y, vc_size_z
    207210
    208     NAMELIST /particles_par/      alloc_factor, bc_par_b, bc_par_lr,           &
    209                                   bc_par_ns, bc_par_t, collision_algorithm,    &
     211    NAMELIST /particles_par/      aero_type, aero_weight, alloc_factor,        &
     212                                  bc_par_b, bc_par_lr,                         &
     213                                  bc_par_ns, bc_par_t,                         &
    210214                                  collision_kernel, curvature_solution_effects,&
    211215                                  deallocate_memory, density_ratio,            &
     
    214218                                  dt_write_particle_data,                      &
    215219                                  end_time_prel, initial_weighting_factor,     &
    216                                   init_aerosol_probabilistic,                  &
     220                                  log_sigma,                                   &
    217221                                  max_number_particles_per_gridbox, merging,   &
    218                                   min_nr_particle, monodisperse_aerosols,      &
    219                                   n1, n2, n3, number_concentration,            &
     222                                  min_nr_particle,                             &
     223                                  na, number_concentration,                    &
    220224                                  number_of_particle_groups,                   &
    221225                                  number_particles_per_gridbox,                &
     
    224228                                  particle_maximum_age, pdx, pdy, pdz, psb,    &
    225229                                  psl, psn, psr, pss, pst, radius,             &
    226                                   radius_classes, radius_merge, radius_split,  &   
     230                                  radius_classes, radius_merge, radius_split,  &
    227231                                  random_start_position,                       &
    228                                   read_particles_from_restartfile,             &
    229                                   rm1, rm2, rm3,                               &
     232                                  read_particles_from_restartfile, rm,         &
    230233                                  seed_follows_topography,                     &
    231234                                  splitting, splitting_factor,                 &
    232235                                  splitting_factor_max, splitting_function,    &
    233                                   splitting_mode, step_dealloc, s1, s2, s3,    &
     236                                  splitting_mode, step_dealloc,                &
    234237                                  use_sgs_for_particles,                       &
    235238                                  vertical_particle_advection,                 &
Note: See TracChangeset for help on using the changeset viewer.