WriteArrivalsBinary Subroutine

public subroutine WriteArrivalsBinary(r, Nrd, Nr, SourceType)

Writes arrival data in binary format

Arguments

Type IntentOptional Attributes Name
real, intent(in) :: r(Nr)
integer, intent(in) :: Nrd
integer, intent(in) :: Nr
character(len=1), intent(in) :: SourceType

Calls

proc~~writearrivalsbinary~~CallsGraph proc~writearrivalsbinary WriteArrivalsBinary sngl sngl proc~writearrivalsbinary->sngl

Called by

proc~~writearrivalsbinary~~CalledByGraph proc~writearrivalsbinary WriteArrivalsBinary proc~bellhopcore~2 BellhopCore proc~bellhopcore~2->proc~writearrivalsbinary program~bellhop BELLHOP program~bellhop->proc~bellhopcore~2

Source Code

  SUBROUTINE WriteArrivalsBinary( r, Nrd, Nr, SourceType )
!! Writes arrival data in binary format

    ! Writes the arrival data (amplitude, delay for each eigenray)
    ! Binary output file

    INTEGER,           INTENT( IN ) :: Nrd, Nr
    REAL,              INTENT( IN ) :: r( Nr )
    CHARACTER (LEN=1), INTENT( IN ) :: SourceType
    INTEGER           :: ir, id, iArr

    WRITE( ARRFile ) MAXVAL( NArr( 1 : Nrd, 1 : Nr ) )

    DO id = 1, Nrd
       DO ir = 1, Nr
          IF ( SourceType == 'X' ) THEN   ! line source
             factor = 4.0 * SQRT( pi )
          ELSE                            ! point source
             IF ( r ( ir ) == 0 ) THEN
                factor = 1e5                   ! avoid /0 at origin
             ELSE
                factor = 1. / SQRT( r( ir ) )  ! cyl. spreading
             END IF
          END IF

          WRITE( ARRFile ) NArr( id, ir )

          DO iArr = 1, NArr( id, ir )
             ! integers written out as reals below for fast reading in Matlab
             WRITE( ARRFile ) &
                  factor * Arr( id, ir, iArr )%A,           &
            SNGL( RadDeg * Arr( id, ir, iArr )%Phase ),       &
                           Arr( id, ir, iArr )%delay,         &
                           Arr( id, ir, iArr )%SrcDeclAngle,  &
                           Arr( id, ir, iArr )%RcvrDeclAngle, &
                     REAL( Arr( id, ir, iArr )%NTopBnc ),     &
                     REAL( Arr( id, ir, iArr )%NBotBnc )

          END DO   ! next arrival
       END DO   ! next receiver depth
    END DO   ! next receiver range

    RETURN
  END SUBROUTINE WriteArrivalsBinary