WriteArrivalsBinary3D Subroutine

public subroutine WriteArrivalsBinary3D(r, Ntheta, Nrd, Nr)

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

Arguments

Type IntentOptional Attributes Name
real, intent(in) :: r(Nr)
integer, intent(in) :: Ntheta
integer, intent(in) :: Nrd
integer, intent(in) :: Nr

Calls

proc~~writearrivalsbinary3d~~CallsGraph proc~writearrivalsbinary3d WriteArrivalsBinary3D sngl sngl proc~writearrivalsbinary3d->sngl

Called by

proc~~writearrivalsbinary3d~~CalledByGraph proc~writearrivalsbinary3d WriteArrivalsBinary3D proc~bellhopcore BellhopCore proc~bellhopcore->proc~writearrivalsbinary3d program~bellhop3d BELLHOP3D program~bellhop3d->proc~bellhopcore

Source Code

  SUBROUTINE WriteArrivalsBinary3D( r, Ntheta, Nrd, Nr )
!! Writes the arrival data (amplitude, delay for each eigenray); Binary output file

    INTEGER, INTENT( IN ) :: Ntheta, Nrd, Nr
    REAL,    INTENT( IN ) :: r( Nr )
    INTEGER               :: itheta, ir, id, iArr

    WRITE( ARRFile ) MAXVAL( NArr3D( 1 : Ntheta,  1 : Nrd, 1 : Nr ) )

    DO itheta = 1, Ntheta
       DO id = 1, Nrd
          DO ir = 1, Nr
             IF ( Beam%RunType( 6 : 6 ) == '2' ) THEN   ! 2D run?
                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 ) NArr3D( itheta,  id, ir )

             DO iArr = 1, NArr3D( itheta,  id, ir )
                ! integers written out as reals below for fast reading in Matlab
                WRITE( ARRFile ) &
                     factor * Arr3D( itheta, id, ir, iArr )%A,             &
               SNGL( RadDeg * Arr3D( itheta, id, ir, iArr )%Phase ),       &
                              Arr3D( itheta, id, ir, iArr )%delay,         &
                              Arr3D( itheta, id, ir, iArr )%SrcDeclAngle,  &
                              Arr3D( itheta, id, ir, iArr )%SrcAzimAngle,  &
                              Arr3D( itheta, id, ir, iArr )%RcvrDeclAngle, &
                              Arr3D( itheta, id, ir, iArr )%RcvrAzimAngle, &
                        REAL( Arr3D( itheta, id, ir, iArr )%NTopBnc ),     &
                        REAL( Arr3D( itheta, id, ir, iArr )%NBotBnc )
             END DO   ! next arrival
          END DO   ! next receiver depth
       END DO   ! next receiver range
    END DO   ! next receiver angle

    RETURN
  END SUBROUTINE WriteArrivalsBinary3D