SUBROUTINE lpm !--------------------------------------------------------------------------------! ! This file is part of PALM. ! ! PALM is free software: you can redistribute it and/or modify it under the terms ! of the GNU General Public License as published by the Free Software Foundation, ! either version 3 of the License, or (at your option) any later version. ! ! PALM is distributed in the hope that it will be useful, but WITHOUT ANY ! WARRANTY; without even the implied warranty of MERCHANTABILITY or FITNESS FOR ! A PARTICULAR PURPOSE. See the GNU General Public License for more details. ! ! You should have received a copy of the GNU General Public License along with ! PALM. If not, see . ! ! Copyright 1997-2012 Leibniz University Hannover !--------------------------------------------------------------------------------! ! ! Current revisions: ! ------------------ ! ! ! Former revisions: ! ----------------- ! $Id: lpm.f90 1037 2012-10-22 14:10:22Z suehring $ ! ! 1036 2012-10-22 13:43:42Z raasch ! code put under GPL (PALM 3.9) ! ! 851 2012-03-15 14:32:58Z raasch ! Bugfix: resetting of particle_mask and tail mask moved from routine ! lpm_exchange_horiz to here (end of sub-timestep loop) ! ! 849 2012-03-15 10:35:09Z raasch ! original routine advec_particles split into several subroutines and renamed ! lpm ! ! 831 2012-02-22 00:29:39Z raasch ! thermal_conductivity_l and diff_coeff_l now depend on temperature and ! pressure ! ! 828 2012-02-21 12:00:36Z raasch ! fast hall/wang kernels with fixed radius/dissipation classes added, ! particle feature color renamed class, routine colker renamed ! recalculate_kernel, ! lower limit for droplet radius changed from 1E-7 to 1E-8 ! ! Bugfix: transformation factor for dissipation changed from 1E5 to 1E4 ! ! 825 2012-02-19 03:03:44Z raasch ! droplet growth by condensation may include curvature and solution effects, ! initialisation of temporary particle array for resorting removed, ! particle attributes speed_x|y|z_sgs renamed rvar1|2|3, ! module wang_kernel_mod renamed lpm_collision_kernels_mod, ! wang_collision_kernel renamed wang_kernel ! ! 799 2011-12-21 17:48:03Z franke ! Implementation of Wang collision kernel and corresponding new parameter ! wang_collision_kernel ! ! 792 2011-12-01 raasch ! particle arrays (particles, particles_temp) implemented as pointers in ! order to speed up sorting (see routine sort_particles) ! ! 759 2011-09-15 13:58:31Z raasch ! Splitting of parallel I/O (routine write_particles) ! ! Revision 1.1 1999/11/25 16:16:06 raasch ! Initial revision ! ! ! Description: ! ------------ ! Particle advection !------------------------------------------------------------------------------! USE arrays_3d USE control_parameters USE cpulog USE interfaces USE particle_attributes USE pegrid USE statistics IMPLICIT NONE INTEGER :: m CALL cpu_log( log_point(25), 'lpm', 'start' ) ! !-- Write particle data at current time on file. !-- This has to be done here, before particles are further processed, !-- because they may be deleted within this timestep (in case that !-- dt_write_particle_data = dt_prel = particle_maximum_age). time_write_particle_data = time_write_particle_data + dt_3d IF ( time_write_particle_data >= dt_write_particle_data ) THEN CALL lpm_data_output_particles ! !-- The MOD function allows for changes in the output interval with restart !-- runs. time_write_particle_data = MOD( time_write_particle_data, & MAX( dt_write_particle_data, dt_3d ) ) ENDIF ! !-- Initialize arrays for marking those particles/tails to be deleted after the !-- (sub-) timestep particle_mask = .TRUE. deleted_particles = 0 IF ( use_particle_tails ) THEN tail_mask = .TRUE. ENDIF deleted_tails = 0 ! !-- Initialize variables used for accumulating the number of particles !-- exchanged between the subdomains during all sub-timesteps (if sgs !-- velocities are included). These data are output further below on the !-- particle statistics file. trlp_count_sum = 0 trlp_count_recv_sum = 0 trrp_count_sum = 0 trrp_count_recv_sum = 0 trsp_count_sum = 0 trsp_count_recv_sum = 0 trnp_count_sum = 0 trnp_count_recv_sum = 0 ! !-- Calculate exponential term used in case of particle inertia for each !-- of the particle groups DO m = 1, number_of_particle_groups IF ( particle_groups(m)%density_ratio /= 0.0 ) THEN particle_groups(m)%exp_arg = & 4.5 * particle_groups(m)%density_ratio * & molecular_viscosity / ( particle_groups(m)%radius )**2 particle_groups(m)%exp_term = EXP( -particle_groups(m)%exp_arg * & dt_3d ) ENDIF ENDDO ! !-- Particle (droplet) growth by condensation/evaporation and collision IF ( cloud_droplets ) THEN ! !-- Reset summation arrays ql_c = 0.0; ql_v = 0.0; ql_vp = 0.0 ! !-- Droplet growth by condensation / evaporation CALL lpm_droplet_condensation ! !-- Particle growth by collision IF ( collision_kernel /= 'none' ) CALL lpm_droplet_collision ENDIF ! !-- If particle advection includes SGS velocity components, calculate the !-- required SGS quantities (i.e. gradients of the TKE, as well as horizontally !-- averaged profiles of the SGS TKE and the resolved-scale velocity variances) IF ( use_sgs_for_particles ) CALL lpm_init_sgs_tke ! !-- Initialize the variable storing the total time that a particle has advanced !-- within the timestep procedure particles(1:number_of_particles)%dt_sum = 0.0 ! !-- Timestep loop for particle advection. !-- This loop has to be repeated until the advection time of every particle !-- (within the total domain!) has reached the LES timestep (dt_3d). !-- In case of including the SGS velocities, the particle timestep may be !-- smaller than the LES timestep (because of the Lagrangian timescale restric- !-- tion) and particles may require to undergo several particle timesteps, !-- before the LES timestep is reached. Because the number of these particle !-- timesteps to be carried out is unknown at first, these steps are carried !-- out in the following infinite loop with exit condition. DO CALL cpu_log( log_point_s(44), 'lpm_advec', 'start' ) ! !-- Initialize the switch used for the loop exit condition checked at the !-- end of this loop. !-- If at least one particle has failed to reach the LES timestep, this !-- switch will be set false. dt_3d_reached_l = .TRUE. ! !-- Particle advection CALL lpm_advec ! !-- Particle reflection from walls CALL lpm_boundary_conds( 'walls' ) ! !-- User-defined actions after the calculation of the new particle position CALL user_lpm_advec ! !-- Find out, if all particles on every PE have completed the LES timestep !-- and set the switch corespondingly #if defined( __parallel ) IF ( collective_wait ) CALL MPI_BARRIER( comm2d, ierr ) CALL MPI_ALLREDUCE( dt_3d_reached_l, dt_3d_reached, 1, MPI_LOGICAL, & MPI_LAND, comm2d, ierr ) #else dt_3d_reached = dt_3d_reached_l #endif CALL cpu_log( log_point_s(44), 'lpm_advec', 'stop' ) ! !-- Increment time since last release IF ( dt_3d_reached ) time_prel = time_prel + dt_3d ! !-- If necessary, release new set of particles IF ( time_prel >= dt_prel .AND. end_time_prel > simulated_time .AND. & dt_3d_reached ) THEN CALL lpm_release_set ! !-- The MOD function allows for changes in the output interval with !-- restart runs. time_prel = MOD( time_prel, MAX( dt_prel, dt_3d ) ) ENDIF ! !-- Horizontal boundary conditions including exchange between subdmains CALL lpm_exchange_horiz ! !-- Apply boundary conditions to those particles that have crossed the top or !-- bottom boundary and delete those particles, which are older than allowed CALL lpm_boundary_conds( 'bottom/top' ) ! !-- Pack particles (eliminate those marked for deletion), !-- determine new number of particles IF ( number_of_particles > 0 .AND. deleted_particles > 0 ) THEN CALL lpm_pack_arrays ENDIF ! !-- Initialize variables for the next (sub-) timestep, i.e. for marking those !-- particles to be deleted after the timestep particle_mask = .TRUE. deleted_particles = 0 IF ( use_particle_tails ) THEN tail_mask = .TRUE. ENDIF deleted_tails = 0 IF ( dt_3d_reached ) EXIT ENDDO ! timestep loop ! !-- Sort particles in the sequence the gridboxes are stored in the memory time_sort_particles = time_sort_particles + dt_3d IF ( time_sort_particles >= dt_sort_particles ) THEN CALL lpm_sort_arrays time_sort_particles = MOD( time_sort_particles, & MAX( dt_sort_particles, dt_3d ) ) ENDIF ! !-- Calculate the new liquid water content for each grid box IF ( cloud_droplets ) CALL lpm_calc_liquid_water_content ! !-- Set particle attributes. !-- Feature is not available if collision is activated, because the respective !-- particle attribute (class) is then used for storing the particle radius !-- class. IF ( collision_kernel == 'none' ) CALL lpm_set_attributes ! !-- Set particle attributes defined by the user CALL user_lpm_set_attributes ! !-- If required, add the current particle positions to the particle tails IF ( use_particle_tails ) CALL lpm_extend_tails ! !-- Write particle statistics (in particular the number of particles !-- exchanged between the subdomains) on file IF ( write_particle_statistics ) CALL lpm_write_exchange_statistics CALL cpu_log( log_point(25), 'lpm', 'stop' ) END SUBROUTINE lpm