Ignore:
Timestamp:
Sep 6, 2017 3:22:27 PM (7 years ago)
Author:
suehring
Message:

Major bugfix in modeling SGS particle speeds.

File:
1 edited

Legend:

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

    r2263 r2417  
    2525! -----------------
    2626! $Id$
     27! Major bugfixes in modeling SGS particle speeds (since revision 1359).
     28! Particle sorting added to distinguish between already completed and
     29! non-completed particles.
     30!
     31! 2263 2017-06-08 14:59:01Z schwenkel
    2732! Implemented splitting and merging algorithm
    2833!
     
    140145
    141146    USE lpm_pack_arrays_mod,                                                   &
    142         ONLY:  lpm_pack_all_arrays
     147        ONLY:  lpm_pack_all_arrays, lpm_sort
    143148
    144149    USE particle_attributes,                                                   &
     
    259264       CALL cpu_log( log_point_s(44), 'lpm_advec', 'pause' )
    260265       
    261        grid_particles(:,:,:)%time_loop_done = .TRUE.
    262266!
    263267!--    If particle advection includes SGS velocity components, calculate the
     
    265269!--    horizontally averaged profiles of the SGS TKE and the resolved-scale
    266270!--    velocity variances)
    267 
    268271       IF ( use_sgs_for_particles  .AND.  .NOT. cloud_droplets )  THEN
    269272          CALL lpm_init_sgs_tke
    270273       ENDIF
     274
     275!
     276!--    In case SGS-particle speed is considered, particles may carry out
     277!--    several particle timesteps. In order to prevent unnecessary
     278!--    treatment of particles that already reached the final time level,
     279!--    particles are sorted into contiguous blocks of finished and
     280!--    not-finished particles, in addition to their already sorting
     281!--    according to their sub-boxes.
     282       IF ( .NOT. first_loop_stride  .AND.  use_sgs_for_particles )            &
     283          CALL lpm_sort
    271284
    272285       DO  i = nxl, nxr
     
    323336!--             optimization is still possible.)
    324337                IF ( topography /= 'flat' .AND. k < nzb_max + 2 )  THEN
    325                    CALL lpm_boundary_conds( 'walls' )
     338                   CALL lpm_boundary_conds( 'walls' )!, i, j, k )
    326339                ENDIF
    327340!
     
    333346!--             the top or bottom boundary and delete those particles, which are
    334347!--             older than allowed
    335                 CALL lpm_boundary_conds( 'bottom/top' )
     348                CALL lpm_boundary_conds( 'bottom/top' ) !, i, j, k )
    336349!
    337350!---            If not all particles of the actual grid cell have reached the
    338 !--             LES timestep, this cell has to to another loop iteration. Due to
    339 !--             the fact that particles can move into neighboring grid cell,
    340 !--             these neighbor cells also have to perform another loop iteration
     351!--             LES timestep, this cell has to do another loop iteration. Due to
     352!--             the fact that particles can move into neighboring grid cells,
     353!--             these neighbor cells also have to perform another loop iteration.
     354!--             Please note, this realization does not work properly if
     355!--             particles move into another subdomain.
    341356                IF ( .NOT. dt_3d_reached_l )  THEN
    342                    ks = MAX(nzb+1,k)
    343                    ke = MIN(nzt,k)
    344                    js = MAX(nys,j)
    345                    je = MIN(nyn,j)
    346                    is = MAX(nxl,i)
    347                    ie = MIN(nxr,i)
     357                   ks = MAX(nzb+1,k-1)
     358                   ke = MIN(nzt,k+1)
     359                   js = MAX(nys,j-1)
     360                   je = MIN(nyn,j+1)
     361                   is = MAX(nxl,i-1)
     362                   ie = MIN(nxr,i+1)
    348363                   grid_particles(ks:ke,js:je,is:ie)%time_loop_done = .FALSE.
     364                ELSE
     365                   grid_particles(k,j,i)%time_loop_done = .TRUE.
    349366                ENDIF
    350367
     
    392409!--    determine new number of particles
    393410       CALL lpm_pack_all_arrays
    394 
    395411!
    396412!--    Initialize variables for the next (sub-) timestep, i.e., for marking
Note: See TracChangeset for help on using the changeset viewer.