Backup method to find the smoothing length via brute force if the optimized method gives 0. It sets the smoothing lengths to the distance between the particle and the ndes-th closest neighbour.
FT 24.11.2021
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer, | intent(in) | :: | a |
Index of the particle whose smoothing length is to be computed |
||
integer, | intent(in) | :: | npart |
Number of particles |
||
double precision, | intent(in), | DIMENSION(3,npart) | :: | pos |
Array containing particle positions |
|
integer, | intent(in) | :: | ndes |
Desired number of neighbours |
Smoothing length
Type | Visibility | Attributes | Name | Initial | |||
---|---|---|---|---|---|---|---|
integer, | public | :: | b |
Particle index running over all particles, except particle |
|||
double precision, | public, | DIMENSION(3) | :: | dist |
Distance vector between the particles |
||
double precision, | public, | DIMENSION(npart) | :: | dist2 |
Square norm of the distance vector between the particles |
FUNCTION find_h_backup( a, npart, pos, ndes ) RESULT( h )
!**************************************************************
!
!# Backup method to find the smoothing length via brute force
! if the optimized method gives 0.
! It sets the smoothing lengths to the distance between the
! particle and the ndes-th closest neighbour.
!
! FT 24.11.2021
!
!**************************************************************
USE NR, ONLY: select
USE constants, ONLY: half
IMPLICIT NONE
INTEGER, INTENT(IN):: a
!! Index of the particle whose smoothing length is to be computed
INTEGER, INTENT(IN):: npart
!! Number of particles
INTEGER, INTENT(IN):: ndes
!! Desired number of neighbours
DOUBLE PRECISION, DIMENSION(3,npart), INTENT(IN):: pos
!! Array containing particle positions
DOUBLE PRECISION:: h
!! Smoothing length
INTEGER:: b
!! Particle index running over all particles, except particle `a`
DOUBLE PRECISION, DIMENSION(npart):: dist2
!! Square norm of the distance vector between the particles `a` and `b`
DOUBLE PRECISION, DIMENSION(3):: dist
!! Distance vector between the particles `a` and `b`
!$OMP PARALLEL DO DEFAULT( NONE ) &
!$OMP SHARED( pos, a, npart, dist2 ) &
!$OMP PRIVATE( b, dist )
DO b= 1, npart, 1
!IF( a /= b )THEN
dist(:)= pos(:,b) - pos(:,a)
dist2(b)= DOT_PRODUCT(dist,dist)
!ENDIF
ENDDO
!$OMP END PARALLEL DO
! ndes+1 is used, rather tan ndes, because the particle itself is included
! in the distance array dist2
h= half*SQRT( select(ndes+1, npart, dist2) )
END FUNCTION find_h_backup