bellhopMod.f90 Source File

Core BELLHOP module with global variables and data structures


This file depends on

sourcefile~~bellhopmod.f90~~EfferentGraph sourcefile~bellhopmod.f90 bellhopMod.f90 sourcefile~mathconstants.f90 MathConstants.f90 sourcefile~bellhopmod.f90->sourcefile~mathconstants.f90

Files dependent on this one

sourcefile~~bellhopmod.f90~~AfferentGraph sourcefile~bellhopmod.f90 bellhopMod.f90 sourcefile~arrmod.f90 ArrMod.f90 sourcefile~arrmod.f90->sourcefile~bellhopmod.f90 sourcefile~bellhop3d.f90 bellhop3D.f90 sourcefile~bellhop3d.f90->sourcefile~bellhopmod.f90 sourcefile~bellhop3d.f90->sourcefile~arrmod.f90 sourcefile~influence.f90 influence.f90 sourcefile~bellhop3d.f90->sourcefile~influence.f90 sourcefile~influence3d.f90 influence3D.f90 sourcefile~bellhop3d.f90->sourcefile~influence3d.f90 sourcefile~readenvironmentbell.f90 ReadEnvironmentBell.f90 sourcefile~bellhop3d.f90->sourcefile~readenvironmentbell.f90 sourcefile~reflect3dmod.f90 Reflect3DMod.f90 sourcefile~bellhop3d.f90->sourcefile~reflect3dmod.f90 sourcefile~reflectmod.f90 ReflectMod.f90 sourcefile~bellhop3d.f90->sourcefile~reflectmod.f90 sourcefile~step3dmod.f90 Step3DMod.f90 sourcefile~bellhop3d.f90->sourcefile~step3dmod.f90 sourcefile~writeray.f90 WriteRay.f90 sourcefile~bellhop3d.f90->sourcefile~writeray.f90 sourcefile~cone.f90 Cone.f90 sourcefile~cone.f90->sourcefile~bellhopmod.f90 sourcefile~influence.f90->sourcefile~bellhopmod.f90 sourcefile~influence.f90->sourcefile~arrmod.f90 sourcefile~influence.f90->sourcefile~writeray.f90 sourcefile~influence3d.f90->sourcefile~bellhopmod.f90 sourcefile~influence3d.f90->sourcefile~arrmod.f90 sourcefile~influence3d.f90->sourcefile~writeray.f90 sourcefile~readenvironmentbell.f90->sourcefile~bellhopmod.f90 sourcefile~reflect3dmod.f90->sourcefile~bellhopmod.f90 sourcefile~reflectmod.f90->sourcefile~bellhopmod.f90 sourcefile~reflectmod.f90->sourcefile~cone.f90 sourcefile~step.f90 Step.f90 sourcefile~step.f90->sourcefile~bellhopmod.f90 sourcefile~step3dmod.f90->sourcefile~bellhopmod.f90 sourcefile~writeray.f90->sourcefile~bellhopmod.f90 sourcefile~bellhop.f90 bellhop.f90 sourcefile~bellhop.f90->sourcefile~arrmod.f90 sourcefile~bellhop.f90->sourcefile~influence.f90 sourcefile~bellhop.f90->sourcefile~readenvironmentbell.f90 sourcefile~bellhop.f90->sourcefile~step.f90 sourcefile~bellhop.f90->sourcefile~writeray.f90

Source Code

!! Core BELLHOP module with global variables and data structures

MODULE bellhopMod
  !! Main BELLHOP module containing global variables, data structures, and types for acoustic ray tracing

  USE MathConstants

  IMPLICIT NONE
  PUBLIC

  INTEGER, PARAMETER :: ENVFile = 5, PRTFile = 6, RAYFile = 21, SHDFile = 25, ARRFile = 36, SSPFile = 40, MaxN = 100000
  LOGICAL, PARAMETER :: STEP_DEBUGGING = .FALSE.

  ! Reduce MaxN (= max # of steps along a ray) to reduce storage
  ! Note space is wasted in NumTopBnc, NumBotBnc ...

  LOGICAL            :: ThreeD   ! flag to indicate BELLHOP vs BELLHOP3D run
  INTEGER            :: Nrz_per_range
  REAL    ( KIND= 8) :: freq, omega, SrcDeclAngle, SrcAzimAngle, xs_3D( 3 )
  CHARACTER (LEN=80) :: Title

  ! *** Beam structure ***

  TYPE rxyz
     REAL (KIND=8) :: r, x, y, z
  END TYPE rxyz

  TYPE BeamStructure
     INTEGER           :: NBeams, Nimage, Nsteps, iBeamWindow
     REAL     (KIND=8) :: deltas, epsMultiplier = 1, rLoop
     CHARACTER (LEN=1) :: Component              ! Pressure or displacement
     CHARACTER (LEN=4) :: Type = 'G S '
     CHARACTER (LEN=7) :: RunType
     TYPE( rxyz )      :: Box
  END TYPE BeamStructure

  TYPE( BeamStructure ) :: Beam

  ! *** ray structure ***

  TYPE ray2DPt
     INTEGER          :: NumTopBnc, NumBotBnc
     REAL   (KIND=8 ) :: x( 2 ), t( 2 ), p( 2 ), q( 2 ), c, Amp, Phase
     COMPLEX (KIND=8) :: tau
  END TYPE ray2DPt
  TYPE( ray2DPt )     :: ray2D( MaxN )

  ! uncomment COMPLEX below if using paraxial beams !!!
  TYPE ray3DPt
     REAL    (KIND=8) :: p_tilde( 2 ), q_tilde( 2 ), p_hat( 2 ), q_hat( 2 ), DetQ
     REAL    (KIND=8) :: x( 3 ), t( 3 ), phi, c, Amp, Phase
     INTEGER          :: NumTopBnc, NumBotBnc
     ! COMPLEX (KIND=8) :: p_tilde( 2 ), q_tilde( 2 ), p_hat( 2 ), q_hat( 2 ), f, g, h, DetP, DetQ
     COMPLEX (KIND=8) :: tau

  END TYPE ray3DPt
  TYPE( ray3DPt )     :: ray3D( MaxN )

END MODULE bellhopMod