is_visible Subroutine

public subroutine is_visible(X, V, threshold_angle, bool, ii, jj)

Arguments

Type IntentOptional AttributesName
real(kind=rp), intent(in), DIMENSION(3):: X
real(kind=rp), intent(in), DIMENSION(3):: V
real(kind=rp), intent(in) :: threshold_angle
logical, intent(out) :: bool
integer, intent(out) :: ii
integer, intent(out) :: jj

Contents

Source Code


Source Code

  SUBROUTINE is_visible(X,V,threshold_angle,bool,ii,jj)
    IMPLICIT NONE
    REAL(rp), DIMENSION(3), INTENT(IN) :: X
    REAL(rp), DIMENSION(3), INTENT(IN) :: V
    REAL(rp), INTENT(IN) :: threshold_angle
    LOGICAL, INTENT(OUT) :: bool
    INTEGER, INTENT(OUT) :: ii
    INTEGER, INTENT(OUT) :: jj
    REAL(rp), DIMENSION(3) :: vec
    REAL(rp), DIMENSION(3) :: n
    REAL(rp) :: r
    REAL(rp) :: psi
    REAL(rp) :: t,ax,ay

    vec(1) = cam%position(1) - X(1)
    vec(2) = -X(2)
    vec(3) = cam%position(2) - X(3)

    r = SQRT(DOT_PRODUCT(vec,vec))
    n = vec/r

    psi = ACOS(DOT_PRODUCT(n,V))

    n = (/vec(1),vec(2),0.0_rp/)
    n = n/SQRT(DOT_PRODUCT(n,n))

    if (psi.LE.threshold_angle) then
       t =  ACOS(DOT_PRODUCT(n,(/1.0_rp,0.0_rp,0.0_rp/)))

       if (cam%incline.GT.0.5_rp*C_PI) then
          if (t.GT.ang%ac) then
             ax = -ACOS(DOT_PRODUCT(n,cam%r))
          else
             ax = ACOS(DOT_PRODUCT(n,cam%r))
          end if
       else
          if (t.GT.ang%ac) then
             ax = ACOS(DOT_PRODUCT(n,cam%r))
          else
             ax = -ACOS(DOT_PRODUCT(n,cam%r))
          end if
       end if

       ay = -ASIN(vec(3)/r)

       if ((ax.GT.ang%max_ax).OR.(ax.LT.ang%min_ax)) then
          bool = .FALSE. ! The particle is not visible
       else if ((ay.GT.ang%max_ay).OR.(ay.LT.ang%min_ay)) then
          bool = .FALSE. ! The particle is not visible
       else
          bool = .TRUE. ! The particle is visible
          ii = MINLOC(ABS(ax - ang%ax),1)
          jj = MINLOC(ABS(ay - ang%ay),1)
       end if
    else
       bool = .FALSE. ! The particle is not visible
    end if
  END SUBROUTINE is_visible