Skip to content

Commit

Permalink
particle module tested
Browse files Browse the repository at this point in the history
  • Loading branch information
fangjian authored and fangjian committed Oct 8, 2024
1 parent 50abde3 commit 5c0159d
Show file tree
Hide file tree
Showing 9 changed files with 1,233 additions and 144 deletions.
4 changes: 1 addition & 3 deletions src/Case-TGV.f90
Original file line number Diff line number Diff line change
Expand Up @@ -108,12 +108,10 @@ subroutine init_tgv (ux1,uy1,uz1,ep1,phi1)
#ifdef DEBG
if (nrank == 0) write(*,*) '# init end ok'
#endif
if(pt_active) call particle_init()
if(particle_active) call particle_init()

call visu_tgv0(rho1, ux1, uy1, uz1, pp3, phi1, ep1)

call visu_particle(itime)

return

end subroutine init_tgv
Expand Down
2 changes: 1 addition & 1 deletion src/case.f90
Original file line number Diff line number Diff line change
Expand Up @@ -504,7 +504,7 @@ subroutine visu_case(rho1,ux1,uy1,uz1,pp3,phi1,ep1,num)

endif

if(pt_active) call visu_particle(itime)
if(particle_active) call visu_particle(itime)

end subroutine visu_case
!##################################################################
Expand Down
2 changes: 1 addition & 1 deletion src/module_param.f90
Original file line number Diff line number Diff line change
Expand Up @@ -332,7 +332,7 @@ module param
real(mytype) :: C_filter
character(len=512) :: inflowpath
logical :: validation_restart
logical :: mhd_active,pt_active
logical :: mhd_active,particle_active

! Logical, true when synchronization is needed
logical, save :: sync_vel_needed = .true.
Expand Down
115 changes: 115 additions & 0 deletions src/mptool.f90
Original file line number Diff line number Diff line change
Expand Up @@ -20,6 +20,11 @@ module mptool
module procedure pmax_mytype
end interface
!
interface ptabupd
module procedure ptable_update_int_arr
module procedure updatable_int
end interface ptabupd
!
interface pwrite
module procedure pwrite_1darray
module procedure pwrite_2darray
Expand Down Expand Up @@ -143,6 +148,95 @@ real(mytype) function pmax_mytype(var)
!
end function pmax_mytype
!
!+-------------------------------------------------------------------+
!| this function is to update table based on alltoall mpi |
!+-------------------------------------------------------------------+
!| CHANGE RECORD |
!| ------------- |
!| 17-Jun-2022 | Created by J. Fang STFC Daresbury Laboratory |
!+-------------------------------------------------------------------+
function ptable_update_int_arr(vain) result(vout)
!
use mpi
!
integer,intent(in) :: vain(:)
integer :: vout(size(vain))
!
! local variables
integer :: nvar,ierr
!
nvar=size(vain)
!
call mpi_alltoall(vain,1,mpi_integer, &
vout,1,mpi_integer,mpi_comm_world,ierr)
!
return
!
end function ptable_update_int_arr
!
function updatable_int(var,offset,debug,comm,comm_size) result(table)
!
use mpi
!
! arguments
integer,allocatable :: table(:)
integer,intent(in) :: var
integer,optional,intent(out) :: offset
logical,intent(in),optional :: debug
integer,intent(in),optional :: comm,comm_size
!
! local data
integer :: comm2use,comm2size
integer :: ierr,i
integer,allocatable :: vta(:)
logical :: ldebug
!
if(present(debug)) then
ldebug=debug
else
ldebug=.false.
endif
!
if(present(comm)) then
comm2use=comm
else
comm2use=mpi_comm_world
endif
!
if(present(comm_size)) then
comm2size=comm_size
else
comm2size=nproc
endif
!
allocate(table(0:comm2size-1),vta(0:comm2size-1))
!
call mpi_allgather(var,1,mpi_integer, &
vta,1,mpi_integer,comm2use,ierr)
!
table=vta
!
if(present(offset)) then
!
if(nrank==0) then
offset=0
else
!
offset=0
do i=0,nrank-1
offset=offset+vta(i)
enddo
!
endif
!
endif
!
end function updatable_int
!
!+-------------------------------------------------------------------+
!| The end of the subroutine ptabupd. |
!+-------------------------------------------------------------------+

pure function cross_product(a,b)
!
real(mytype) :: cross_product(3)
Expand Down Expand Up @@ -449,4 +543,25 @@ integer function prelay(number)

end function prelay
!
function linintp(xx1,xx2,yy1,yy2,xx) result(yy)
!
real(8),intent(in) :: xx1,xx2,xx
real(8),intent(in) :: yy1(:,:,:),yy2(:,:,:)
real(8) :: yy(1:size(yy1,1),1:size(yy1,2),1:size(yy1,3))
!
real(8) :: var1
!
if(abs(xx-xx1)<1.d-16) then
yy=yy1
elseif(abs(xx-xx2)<1.d-16) then
yy=yy2
else
var1=(xx-xx1)/(xx2-xx1)
yy=(yy2-yy1)*var1+yy1
endif
!
return
!
end function linintp

end module mptool
4 changes: 2 additions & 2 deletions src/parameters.f90
Original file line number Diff line number Diff line change
Expand Up @@ -48,7 +48,7 @@ subroutine parameter(input_i3d)
ivisu, ipost, &
gravx, gravy, gravz, &
cpg, idir_stream, &
ifilter, C_filter, iturbine, mhd_active, pt_active, FreeStream
ifilter, C_filter, iturbine, mhd_active, particle_active, FreeStream

NAMELIST /NumOptions/ ifirstder, isecondder, itimescheme, iimplicit, &
nu0nu, cnu, ipinter
Expand Down Expand Up @@ -710,7 +710,7 @@ subroutine parameter_defaults()
hartmann = zero

! particle tracking
pt_active=.false.
particle_active=.false.

!! LES stuff
smagwalldamp=1
Expand Down
Loading

0 comments on commit 5c0159d

Please sign in to comment.