Ignore:
Timestamp:
Dec 1, 2011 12:23:23 AM (12 years ago)
Author:
raasch
Message:

further adjustments for speedup of particle code

File:
1 edited

Legend:

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

    r760 r792  
    44! Current revisions:
    55! ------------------
    6 !
     6! particle arrays (particles, particles_temp) implemented as pointers in
     7! order to speed up sorting (see routine sort_particles)
    78!
    89! Former revisions:
     
    39953996    INTEGER ::  i, ilow, j, k, n
    39963997
    3997     TYPE(particle_type), DIMENSION(1:number_of_particles) ::  particles_temp
     3998    TYPE(particle_type), DIMENSION(:), POINTER ::  particles_temp
    39983999
    39994000
     
    40014002
    40024003!
    4003 !-- Initialize the array used for counting and indexing the particles
    4004     prt_count = 0
     4004!-- Initialize counters and set pointer of the temporary array into which
     4005!-- particles are sorted to free memory
     4006    prt_count  = 0
     4007    sort_count = sort_count +1
     4008
     4009    SELECT CASE ( MOD( sort_count, 2 ) )
     4010
     4011       CASE ( 0 )
     4012
     4013          particles_temp => part_1
     4014          part_1 = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
     4015                                  0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
     4016                                  0.0, 0, 0, 0, 0 )
     4017
     4018       CASE ( 1 )
     4019
     4020          particles_temp => part_2
     4021          part_2 = particle_type( 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
     4022                                  0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, 0.0, &
     4023                                  0.0, 0, 0, 0, 0 )
     4024
     4025    END SELECT
    40054026
    40064027!
     
    40554076    ENDDO
    40564077
    4057     particles(1:number_of_particles) = particles_temp
     4078!
     4079!-- Redirect the particles pointer to the sorted array
     4080    SELECT CASE ( MOD( sort_count, 2 ) )
     4081
     4082       CASE ( 0 )
     4083
     4084          particles => part_1
     4085
     4086       CASE ( 1 )
     4087
     4088          particles => part_2
     4089
     4090    END SELECT
    40584091
    40594092!
Note: See TracChangeset for help on using the changeset viewer.