SUBROUTINE EvaluateSSP3D( x, t, c, cimag, gradc, cxx, cyy, czz, cxy, cxz, cyz, rho, freq, Task )
! Call the particular profil routine indicated by the SSP%Type and perform Task
! Task = 'TAB' then tabulate cp, cs, rhoT
! Task = 'INI' then initialize
REAL (KIND=8), INTENT( IN ) :: freq
REAL (KIND=8), INTENT( IN ) :: x( 3 ) ! x-y-z coordinate where SSP is to be evaluated
REAL (KIND=8), INTENT( IN ) :: t( 3 ) ! ray tangent; for edge cases of updating segments
CHARACTER ( LEN=3), INTENT( IN ) :: Task
REAL (KIND=8), INTENT( OUT ) :: c, cimag, gradc( 3 ), cxx, cyy, czz, cxy, cxz, cyz, rho
REAL (KIND=8) :: x_rz( 2 ), t_rz( 2 ), gradc_rz( 2 ), crr, crz
x_rz = [ 0.0D0, x( 3 ) ] ! convert x-y-z coordinate to cylindrical coordinate
t_rz = [ 0.0D0, t( 3 ) ]
SELECT CASE ( SSP%Type )
CASE ( 'N' )
CALL n2Linear( x_rz, t_rz, c, cimag, gradc_rz, crr, crz, czz, rho, freq, Task )
CASE ( 'C' )
CALL cLinear( x_rz, t_rz, c, cimag, gradc_rz, crr, crz, czz, rho, freq, Task )
CASE ( 'S' )
CALL cCubic( x_rz, t_rz, c, cimag, gradc_rz, crr, crz, czz, rho, freq, Task )
CASE ( 'H' )
CALL Hexahedral( x, t, c, cimag, gradc, cxx, cyy, czz, cxy, cxz, cyz, rho, freq, Task )
CASE ( 'A' )
CALL Analytic3D( x, t, c, cimag, gradc, cxx, cyy, czz, cxy, cxz, cyz, rho )
CASE DEFAULT
WRITE( PRTFile, * ) 'Profile option: ', SSP%Type
CALL ERROUT( 'BELLHOP3D: EvaluateSSP3D', 'Invalid profile option' )
END SELECT
SELECT CASE ( SSP%Type )
CASE ( 'N', 'C', 'S' )
gradc = [ 0.0D0, 0.0D0, gradc_rz( 2 ) ]
cxx = 0.0D0
cyy = 0.0D0
cxy = 0.0D0
cxz = 0.0D0
cyz = 0.0D0
END SELECT
END SUBROUTINE EvaluateSSP3D