Ignore:
Timestamp:
Jul 6, 2017 11:18:47 AM (7 years ago)
Author:
hoffmann
Message:

Improved calculation of particle IDs.

File:
1 edited

Legend:

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

    r2274 r2305  
    2525! -----------------
    2626! $Id$
     27! Improved calculation of particle IDs.
     28!
     29! 2274 2017-06-09 13:27:48Z Giersch
    2730!  Changed error messages
    2831!
     
    4447! 2182 2017-03-17 14:27:40Z schwenkel
    4548! Added parameters for simplified particle initialization.
    46 ! 
     49!
    4750! 2122 2017-01-18 12:22:54Z hoffmann
    4851! Improved initialization of equilibrium aerosol radii
     
    157160 MODULE lpm_init_mod
    158161 
     162    USE, INTRINSIC ::  ISO_C_BINDING
    159163
    160164    USE arrays_3d,                                                             &
     
    187191                ibc_par_lr, ibc_par_ns, ibc_par_t, iran_part, log_z_z0,        &
    188192                max_number_of_particle_groups, min_nr_particle,                &
    189                 mpi_particle_type, number_concentration,                       &
     193                number_concentration,                                          &
    190194                number_particles_per_gridbox,  number_of_particles,            &
    191195                number_of_particle_groups, number_of_sublayers,                &
     
    243247    INTEGER(iwp) ::  k                           !<
    244248
    245 #if defined( __parallel )
    246     INTEGER(iwp), DIMENSION(3) ::  blocklengths  !<
    247     INTEGER(iwp), DIMENSION(3) ::  displacements !<
    248     INTEGER(iwp), DIMENSION(3) ::  types         !<
    249 #endif
    250 
    251249    REAL(wp) ::  div                             !<
    252250    REAL(wp) ::  height_int                      !<
     
    255253    REAL(wp) ::  z0_av_local                     !<
    256254
    257 #if defined( __parallel )
    258 !
    259 !-- Define MPI derived datatype for FORTRAN datatype particle_type (see module
    260 !-- particle_attributes). Integer length is 4 byte, Real is 8 byte
    261     blocklengths(1)  = 19;  blocklengths(2)  =   6;  blocklengths(3)  =   1
    262     displacements(1) =  0;  displacements(2) = 152;  displacements(3) = 176
    263 
    264     types(1) = MPI_REAL
    265     types(2) = MPI_INTEGER
    266     types(3) = MPI_UB
    267     CALL MPI_TYPE_STRUCT( 3, blocklengths, displacements, types, &
    268                           mpi_particle_type, ierr )
    269     CALL MPI_TYPE_COMMIT( mpi_particle_type, ierr )
    270 #endif
    271255
    272256!
     
    541525!
    542526!--    initialize counter for particle IDs
    543        grid_particles%id_counter = 0
     527       grid_particles%id_counter = 1
    544528
    545529!
     
    551535                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,  &
    552536                                      0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp,          &
    553                                       0, 0, 0, 0, .FALSE., -1 )
     537                                      0, 0, 0_idp, .FALSE., -1 )
    554538
    555539       particle_groups = particle_groups_type( 0.0_wp, 0.0_wp, 0.0_wp, 0.0_wp )
     
    697681
    698682                            DO  j = 1, particles_per_point
     683
    699684
    700685                               n = n + 1
     
    731716                               tmp_particle%class         = 1
    732717                               tmp_particle%group         = i
    733                                tmp_particle%id1           = 0
    734                                tmp_particle%id2           = 0
     718                               tmp_particle%id            = 0_idp
    735719                               tmp_particle%particle_mask = .TRUE.
    736720                               tmp_particle%block_nr      = -1
     
    858842             DO  n = local_start(kp,jp,ip), number_of_particles  !only new particles
    859843
    860                 particles(n)%id1 = 10000_iwp * grid_particles(kp,jp,ip)%id_counter + kp
    861                 particles(n)%id2 = 10000_iwp * jp + ip
    862 
     844                particles(n)%id = 10000_idp**3 * grid_particles(kp,jp,ip)%id_counter + &
     845                                  10000_idp**2 * kp + 10000_idp * jp + ip
     846!
     847!--             Count the number of particles that have been released before
    863848                grid_particles(kp,jp,ip)%id_counter =                          &
    864849                                         grid_particles(kp,jp,ip)%id_counter + 1
Note: See TracChangeset for help on using the changeset viewer.