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_exchange_horiz.f90

    r2245 r2305  
    2525! -----------------
    2626! $Id$
     27! Improved calculation of particle IDs.
     28!
     29! 2245 2017-06-02 14:37:10Z schwenkel
    2730! Bugfix in Add_particles_to_gridcell:
    2831! Apply boundary conditions also in y-direction
     
    106109 MODULE lpm_exchange_horiz_mod
    107110 
     111    USE, INTRINSIC ::  ISO_C_BINDING
    108112
    109113    USE control_parameters,                                                    &
     
    130134        ONLY:  alloc_factor, deleted_particles, grid_particles,                &
    131135               ibc_par_lr, ibc_par_ns, min_nr_particle,                        &
    132                mpi_particle_type, number_of_particles,                         &
     136               number_of_particles,                                            &
    133137               offset_ocean_nzt, offset_ocean_nzt_m1, particles,               &
    134138               particle_type, prt_count, trlp_count_sum,                       &
     
    195199    INTEGER(iwp) ::  kp                !< index variable along z
    196200    INTEGER(iwp) ::  n                 !< particle index variable
     201    INTEGER(iwp) ::  par_size          !< Particle size in bytes
    197202    INTEGER(iwp) ::  trlp_count        !< number of particles send to left PE
    198203    INTEGER(iwp) ::  trlp_count_recv   !< number of particles receive from right PE
     
    419424
    420425       ALLOCATE(rvrp(MAX(1,trrp_count_recv)))
    421 
    422        CALL MPI_SENDRECV( trlp(1)%radius, max(1,trlp_count), mpi_particle_type,&
    423                           pleft, 1, rvrp(1)%radius,                            &
    424                           max(1,trrp_count_recv), mpi_particle_type, pright, 1,&
     426!     
     427!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
     428!--    variables in structure particle_type (due to the calculation of par_size)
     429       par_size = c_sizeof(trlp(1))
     430       CALL MPI_SENDRECV( trlp, max(1,trlp_count)*par_size, MPI_BYTE,&
     431                          pleft, 1, rvrp,                            &
     432                          max(1,trrp_count_recv)*par_size, MPI_BYTE, pright, 1,&
    425433                          comm2d, status, ierr )
    426434
     
    436444
    437445       ALLOCATE(rvlp(MAX(1,trlp_count_recv)))
    438 
    439        CALL MPI_SENDRECV( trrp(1)%radius, max(1,trrp_count), mpi_particle_type,&
    440                           pright, 1, rvlp(1)%radius,                           &
    441                           max(1,trlp_count_recv), mpi_particle_type, pleft, 1, &
     446!     
     447!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
     448!--    variables in structure particle_type (due to the calculation of par_size)
     449       par_size = c_sizeof(trrp(1))
     450       CALL MPI_SENDRECV( trrp, max(1,trrp_count)*par_size, MPI_BYTE,&
     451                          pright, 1, rvlp,                           &
     452                          max(1,trlp_count_recv)*par_size, MPI_BYTE, pleft, 1, &
    442453                          comm2d, status, ierr )
    443454
     
    641652
    642653       ALLOCATE(rvnp(MAX(1,trnp_count_recv)))
    643  
    644        CALL MPI_SENDRECV( trsp(1)%radius, trsp_count, mpi_particle_type,      &
    645                           psouth, 1, rvnp(1)%radius,                             &
    646                           trnp_count_recv, mpi_particle_type, pnorth, 1,   &
     654!     
     655!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
     656!--    variables in structure particle_type (due to the calculation of par_size)
     657       par_size = c_sizeof(trsp(1))
     658       CALL MPI_SENDRECV( trsp, trsp_count*par_size, MPI_BYTE,      &
     659                          psouth, 1, rvnp,                             &
     660                          trnp_count_recv*par_size, MPI_BYTE, pnorth, 1,   &
    647661                          comm2d, status, ierr )
    648662
     
    658672
    659673       ALLOCATE(rvsp(MAX(1,trsp_count_recv)))
    660 
    661        CALL MPI_SENDRECV( trnp(1)%radius, trnp_count, mpi_particle_type,      &
    662                           pnorth, 1, rvsp(1)%radius,                          &
    663                           trsp_count_recv, mpi_particle_type, psouth, 1,   &
     674!     
     675!--    This MPI_SENDRECV should work even with odd mixture on 32 and 64 Bit
     676!--    variables in structure particle_type (due to the calculation of par_size)
     677       par_size = c_sizeof(trnp(1))
     678       CALL MPI_SENDRECV( trnp, trnp_count*par_size, MPI_BYTE,      &
     679                          pnorth, 1, rvsp,                          &
     680                          trsp_count_recv*par_size, MPI_BYTE, psouth, 1,   &
    664681                          comm2d, status, ierr )
    665682
Note: See TracChangeset for help on using the changeset viewer.