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

    r2101 r2417  
    2525! -----------------
    2626! $Id$
     27! Particle loops adapted for sub-box structure, i.e. for each sub-box the
     28! particle loop runs from start_index up to end_index instead from 1 to
     29! number_of_particles.
     30!
     31! 2101 2017-01-05 16:42:31Z suehring
    2732!
    2833! 2000 2016-08-20 18:09:15Z knoop
     
    7075    IMPLICIT NONE
    7176
    72     INTEGER(iwp) ::  ip   !<
    73     INTEGER(iwp) ::  jp   !<
    74     INTEGER(iwp) ::  kp   !<
    75     INTEGER(iwp) ::  n    !<
     77    INTEGER(iwp) ::  ip   !< index of particle grid box, x-direction
     78    INTEGER(iwp) ::  jp   !< index of particle grid box, y-direction
     79    INTEGER(iwp) ::  kp   !< index of particle grid box, z-direction
     80    INTEGER(iwp) ::  n    !< particle index
     81    INTEGER(iwp) ::  nb   !< index of sub-box particles are sorted in
     82
     83    INTEGER(iwp), DIMENSION(0:7)  ::  start_index !< start particle index for current sub-box
     84    INTEGER(iwp), DIMENSION(0:7)  ::  end_index   !< start particle index for current sub-box
    7685
    7786!
     
    7988!   number_of_particles = prt_count(kp,jp,ip)
    8089!   particles => grid_particles(kp,jp,ip)%particles(1:number_of_particles)
     90!
     91!   start_index = grid_particles(kp,jp,ip)%start_index
     92!   end_index   = grid_particles(kp,jp,ip)%end_index
     93!
    8194!   IF ( number_of_particles <= 0 )  CYCLE
    8295!   DO  n = 1, number_of_particles
    83 !
     96!   DO  nb = 0, 7
     97!      DO  n = start_index(nb), end_index(nb)
     98!         particles(n)%xxx =
     99!      ENDDO
    84100!   ENDDO
    85101
Note: See TracChangeset for help on using the changeset viewer.