Skip to content

Commit

Permalink
This resolves issue #146 in development_branch
Browse files Browse the repository at this point in the history
This commit substitutes mpi_logical functions with integer
analogues where needed.
  • Loading branch information
palkinev committed Jan 13, 2020
1 parent 80ed231 commit 8efc1a6
Show file tree
Hide file tree
Showing 17 changed files with 19 additions and 272 deletions.
2 changes: 0 additions & 2 deletions Sources/Process/Backup_Mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -30,7 +30,6 @@ module Backup_Mod
include 'Backup_Mod/Read_Face.f90'
include 'Backup_Mod/Read_Int.f90'
include 'Backup_Mod/Read_Int_Array.f90'
include 'Backup_Mod/Read_Log_Array.f90'
include 'Backup_Mod/Read_Real.f90'
include 'Backup_Mod/Read_Real_Array.f90'
include 'Backup_Mod/Read_Swarm.f90'
Expand All @@ -42,7 +41,6 @@ module Backup_Mod
include 'Backup_Mod/Write_Face.f90'
include 'Backup_Mod/Write_Int.f90'
include 'Backup_Mod/Write_Int_Array.f90'
include 'Backup_Mod/Write_Log_Array.f90'
include 'Backup_Mod/Write_Real.f90'
include 'Backup_Mod/Write_Real_Array.f90'
include 'Backup_Mod/Write_Swarm.f90'
Expand Down
52 changes: 0 additions & 52 deletions Sources/Process/Backup_Mod/Read_Log_Array.f90

This file was deleted.

4 changes: 2 additions & 2 deletions Sources/Process/Backup_Mod/Read_Swarm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,15 +26,15 @@ subroutine Backup_Mod_Read_Swarm(fh, disp, vc, swr)
call Backup_Mod_Read_Int(fh, disp, vc, 'n_particles', n_part)

i_work(:) = 0
l_work(:) = .false.
l_work(:) = 0
r_work(:) = 0.0

if(n_part > 0) then
swr % n_particles = n_part
call Backup_Mod_Read_Int_Array(fh, disp, vc, &
'particle_int_data', &
i_work(1:N_I_VARS*swr % n_particles))
call Backup_Mod_Read_Log_Array(fh, disp, vc, &
call Backup_Mod_Read_Int_Array(fh, disp, vc, &
'particle_log_data', &
l_work(1:N_L_VARS*swr % n_particles))
call Backup_Mod_Read_Real_Array(fh, disp, vc, &
Expand Down
29 changes: 0 additions & 29 deletions Sources/Process/Backup_Mod/Write_Log_Array.f90

This file was deleted.

4 changes: 2 additions & 2 deletions Sources/Process/Backup_Mod/Write_Swarm.f90
Original file line number Diff line number Diff line change
Expand Up @@ -26,7 +26,7 @@ subroutine Backup_Mod_Write_Swarm(fh, disp, vc, swr)
call Backup_Mod_Write_Int(fh, disp, vc, 'n_particles', swr % n_particles)

i_work(:) = 0
l_work(:) = .false.
l_work(:) = 0
r_work(:) = 0.0

! Pack particle data in arrays
Expand Down Expand Up @@ -67,7 +67,7 @@ subroutine Backup_Mod_Write_Swarm(fh, disp, vc, swr)
call Backup_Mod_Write_Int_Array(fh, disp, vc, &
'particle_int_data', &
i_work(1:N_I_VARS*swr % n_particles))
call Backup_Mod_Write_Log_Array(fh, disp, vc, &
call Backup_Mod_Write_Int_Array(fh, disp, vc, &
'particle_log_data', &
l_work(1:N_L_VARS*swr % n_particles))
call Backup_Mod_Write_Real_Array(fh, disp, vc, &
Expand Down
6 changes: 3 additions & 3 deletions Sources/Process/Swarm_Mod.f90
Original file line number Diff line number Diff line change
Expand Up @@ -62,8 +62,8 @@ module Swarm_Mod
real :: ft_x, ft_y, ft_z ! total force

! Particle deposition and departure from domain
logical :: deposited
logical :: escaped
integer :: deposited
integer :: escaped

! Particle inside the subdomain
integer :: proc
Expand Down Expand Up @@ -112,7 +112,7 @@ module Swarm_Mod
integer, parameter :: N_L_VARS = 2
integer, parameter :: N_R_VARS = 8
integer, allocatable :: i_work(:)
logical, allocatable :: l_work(:)
integer, allocatable :: l_work(:) ! 0 or 1
real, allocatable :: r_work(:)

contains
Expand Down
12 changes: 6 additions & 6 deletions Sources/Process/Swarm_Mod/Advance_Particles.f90
Original file line number Diff line number Diff line change
Expand Up @@ -12,8 +12,8 @@ subroutine Swarm_Mod_Advance_Particles(swarm, turb)
type(Grid_Type), pointer :: grid
type(Field_Type), pointer :: flow
type(Particle_Type), pointer :: part
logical, pointer :: escaped
logical, pointer :: deposited
integer, pointer :: escaped
integer, pointer :: deposited
integer :: ss ! sub-step counter
integer :: n_parts_in_buffers
!==============================================================================!
Expand Down Expand Up @@ -41,10 +41,10 @@ subroutine Swarm_Mod_Advance_Particles(swarm, turb)
escaped => part % escaped
deposited => part % deposited

!-------------------------------------------------!
! If particle is neither deposited nor escped !
!-------------------------------------------------!
if(.not. deposited .and. .not. escaped) then
!--------------------------------------------------!
! If particle is neither deposited nor escaped !
!--------------------------------------------------!
if( deposited .ne. 1 .and. escaped .ne. 1) then

! If particle is in this processor, carry on with it
if(part % proc .eq. this_proc) then
Expand Down
4 changes: 2 additions & 2 deletions Sources/Process/Swarm_Mod/Allocate.f90
Original file line number Diff line number Diff line change
Expand Up @@ -62,8 +62,8 @@ subroutine Swarm_Mod_Allocate(swarm, flow)
! Assume particle is in the domain
! (A smarter way could be worked out, depending ...
! ... on the result of the call to Find_Nearest_Cell)
swarm % particle(k) % deposited = .false.
swarm % particle(k) % escaped = .false.
swarm % particle(k) % deposited = 0
swarm % particle(k) % escaped = 0

! Is particle in this processor?
swarm % particle(k) % proc = 0
Expand Down
8 changes: 4 additions & 4 deletions Sources/Process/Swarm_Mod/Bounce_Particle.f90
Original file line number Diff line number Diff line change
Expand Up @@ -10,8 +10,8 @@ subroutine Swarm_Mod_Bounce_Particle(swarm, k)
!-----------------------------------[Locals]-----------------------------------!
type(Grid_Type), pointer :: grid
type(Particle_Type), pointer :: part
logical, pointer :: deposited ! part. deposition flag
logical, pointer :: escaped ! part. departure flag
integer, pointer :: deposited ! part. deposition flag
integer, pointer :: escaped ! part. departure flag
integer :: c, c2, s ! nearest cells, face
real :: vel_dot_n
real :: rx_nx_o, ry_ny_o, rz_nz_o, &
Expand Down Expand Up @@ -123,7 +123,7 @@ subroutine Swarm_Mod_Bounce_Particle(swarm, k)

! Trap condition (deposition)
if(swarm % rst <= TINY .or. abs(vel_dot_n) <= 1.0e-3) then
deposited = .true.
deposited = 1
swarm % cnt_d = swarm % cnt_d + 1
print *, k, 'Particle is deposited at: ', xi, yi, zi, f

Expand Down Expand Up @@ -163,7 +163,7 @@ subroutine Swarm_Mod_Bounce_Particle(swarm, k)
! The boundary cell is an outlet !
!------------------------------------!
if(Grid_Mod_Bnd_Cond_Type(grid, c2) == OUTFLOW) then
escaped = .true.
escaped = 1
swarm % cnt_e = swarm % cnt_e + 1
print *, k, 'Particle escaped from outlet at: ', xi, yi, zi, f
end if ! it is an outflow
Expand Down
27 changes: 0 additions & 27 deletions Sources/Shared/Comm_Mod/Parallel/Global_Lor_Log_Array.f90

This file was deleted.

38 changes: 0 additions & 38 deletions Sources/Shared/Comm_Mod/Parallel/Read_Log_Array.f90

This file was deleted.

38 changes: 0 additions & 38 deletions Sources/Shared/Comm_Mod/Parallel/Write_Log_Array.f90

This file was deleted.

12 changes: 0 additions & 12 deletions Sources/Shared/Comm_Mod/Sequential/Global_Lor_Log_Array.f90

This file was deleted.

25 changes: 0 additions & 25 deletions Sources/Shared/Comm_Mod/Sequential/Read_Log_Array.f90

This file was deleted.

22 changes: 0 additions & 22 deletions Sources/Shared/Comm_Mod/Sequential/Write_Log_Array.f90

This file was deleted.

Loading

0 comments on commit 8efc1a6

Please sign in to comment.