AddArr Subroutine

public subroutine AddArr(omega, id, ir, Amp, Phase, delay, SrcDeclAngle, RcvrDeclAngle, NumTopBnc, NumBotBnc)

Adds an arrival to the arrival data structure

Arguments

Type IntentOptional Attributes Name
real(kind=8), intent(in) :: omega
integer, intent(in) :: id
integer, intent(in) :: ir
real(kind=8), intent(in) :: Amp
real(kind=8), intent(in) :: Phase
complex(kind=8), intent(in) :: delay
real(kind=8), intent(in) :: SrcDeclAngle
real(kind=8), intent(in) :: RcvrDeclAngle
integer, intent(in) :: NumTopBnc
integer, intent(in) :: NumBotBnc

Calls

proc~~addarr~~CallsGraph proc~addarr AddArr sngl sngl proc~addarr->sngl

Called by

proc~~addarr~~CalledByGraph proc~addarr AddArr proc~applycontribution~2 ApplyContribution proc~applycontribution~2->proc~addarr proc~influencegeogaussiancart InfluenceGeoGaussianCart proc~influencegeogaussiancart->proc~applycontribution~2 proc~influencegeohatcart InfluenceGeoHatCart proc~influencegeohatcart->proc~applycontribution~2 proc~influencegeohatraycen InfluenceGeoHatRayCen proc~influencegeohatraycen->proc~applycontribution~2 proc~influencesgb InfluenceSGB proc~influencesgb->proc~applycontribution~2 proc~bellhopcore BellhopCore proc~bellhopcore->proc~influencegeogaussiancart proc~bellhopcore->proc~influencegeohatcart proc~bellhopcore->proc~influencegeohatraycen proc~bellhopcore->proc~influencesgb proc~bellhopcore~2 BellhopCore proc~bellhopcore~2->proc~influencegeogaussiancart proc~bellhopcore~2->proc~influencegeohatcart proc~bellhopcore~2->proc~influencegeohatraycen proc~bellhopcore~2->proc~influencesgb program~bellhop BELLHOP program~bellhop->proc~bellhopcore~2 program~bellhop3d BELLHOP3D program~bellhop3d->proc~bellhopcore

Source Code

  SUBROUTINE AddArr( omega, id, ir, Amp, Phase, delay, SrcDeclAngle, RcvrDeclAngle, NumTopBnc, NumBotBnc )
!! Adds an arrival to the arrival data structure

    ! Adds the amplitude and delay for an ARRival into a matrix of same.
    ! Extra logic included to keep only the strongest arrivals.

    INTEGER,              INTENT( IN ) :: NumTopBnc, NumBotBnc, id, ir
    REAL    ( KIND = 8 ), INTENT( IN ) :: omega, Amp, Phase, SrcDeclAngle, RcvrDeclAngle
    COMPLEX ( KIND = 8 ), INTENT( IN ) :: delay
    LOGICAL              :: NewRay
    INTEGER              :: iArr( 1 ), Nt
    REAL                 :: AmpTot, w1, w2

    Nt     = NArr( id, ir )    ! # of arrivals
    NewRay = .TRUE.

    ! Is this the second step of a pair (on the same ray)?
    ! If so, we want to combine the arrivals to conserve space.
    ! (test this by seeing if the arrival time is close to the previous one)
    ! (also need that the phase is about the same to make sure surface and direct paths are not joined)
    ! LP: BUG: This only checks the last arrival, whereas the first step of the
    ! pair could have been placed in previous slots. See readme.

    IF ( Nt >= 1 ) THEN
       IF ( omega * ABS( delay - Arr( id, ir, Nt )%delay ) < PhaseTol .AND. &
           ABS( Arr( id, ir, Nt )%phase - Phase )       < PhaseTol ) NewRay = .FALSE.
    END IF

    IF ( NewRay ) THEN
       IF ( Nt >= MaxNArr ) THEN       ! space not available to add an arrival?
          iArr = MINLOC( Arr( id, ir, : )%A )                       ! replace weakest arrival
          IF ( Amp > Arr( id, ir, iArr( 1 ) )%A ) THEN
             Arr( id, ir, iArr( 1 ) )%A             = SNGL( Amp )       ! amplitude
             Arr( id, ir, iArr( 1 ) )%Phase         = SNGL( Phase )     ! phase
             Arr( id, ir, iArr( 1 ) )%delay         = CMPLX( delay )    ! delay time
             Arr( id, ir, iArr( 1 ) )%SrcDeclAngle  = SNGL( SrcDeclAngle )  ! launch angle from source
             Arr( id, ir, iArr( 1 ) )%RcvrDeclAngle = SNGL( RcvrDeclAngle ) ! angle ray reaches receiver
             Arr( id, ir, iArr( 1 ) )%NTopBnc       = NumTopBnc         ! Number of top     bounces
             Arr( id, ir, iArr( 1 ) )%NBotBnc       = NumBotBnc         !   "       bottom
          ENDIF
       ELSE
          NArr( id, ir         )               = Nt + 1              ! # of arrivals
          Arr(  id, ir, Nt + 1 )%A             = SNGL( Amp )         ! amplitude
          Arr(  id, ir, Nt + 1 )%Phase         = SNGL( Phase )       ! phase
          Arr(  id, ir, Nt + 1 )%delay         = CMPLX( delay )      ! delay time
          Arr(  id, ir, Nt + 1 )%SrcDeclAngle  = SNGL( SrcDeclAngle )    ! launch angle from source
          Arr(  id, ir, Nt + 1 )%RcvrDeclAngle = SNGL( RcvrDeclAngle )   ! angle ray reaches receiver
          Arr(  id, ir, Nt + 1 )%NTopBnc       = NumTopBnc           ! Number of top     bounces
          Arr(  id, ir, Nt + 1 )%NBotBnc       = NumBotBnc           !   "       bottom
       ENDIF
    ELSE      ! not a new ray
       !PhaseArr(   id, ir, Nt ) = PhaseArr( id, ir, Nt )

       ! calculate weightings of old ray information vs. new, based on amplitude of the arrival
       AmpTot = Arr( id, ir, Nt )%A + SNGL( Amp )
       w1     = Arr( id, ir, Nt )%A / AmpTot
       w2     = REAL( Amp ) / AmpTot

       Arr( id, ir, Nt )%delay         = w1 * Arr( id, ir, Nt )%delay         + w2 * CMPLX( delay ) ! weighted sum
       Arr( id, ir, Nt )%A             = AmpTot
       Arr( id, ir, Nt )%SrcDeclAngle  = w1 * Arr( id, ir, Nt )%SrcDeclAngle  + w2 * SNGL( SrcDeclAngle  )
       Arr( id, ir, Nt )%RcvrDeclAngle = w1 * Arr( id, ir, Nt )%RcvrDeclAngle + w2 * SNGL( RcvrDeclAngle )
    ENDIF

    RETURN
  END SUBROUTINE AddArr