module Numeric.GSL.Special.Trig(
  sin_e
, Numeric.GSL.Special.Trig.sin
, cos_e
, Numeric.GSL.Special.Trig.cos
, hypot_e
, hypot
, complex_sin_e
, complex_cos_e
, complex_logsin_e
, sinc_e
, sinc
, lnsinh_e
, lnsinh
, lncosh_e
, lncosh
, polar_to_rect
, rect_to_polar
, sin_err_e
, cos_err_e
, angle_restrict_symm
, angle_restrict_pos
, angle_restrict_symm_err_e
, angle_restrict_pos_err_e
) where
import Foreign(Ptr)
import Foreign.C.Types
import Numeric.GSL.Special.Internal
sin_e :: Double -> (Double,Double)
sin_e x = createSFR "sin_e" $ gsl_sf_sin_e x
foreign import ccall SAFE_CHEAP "gsl_sf_sin_e" gsl_sf_sin_e :: Double -> Ptr () -> IO CInt
sin :: Double -> Double
sin = gsl_sf_sin
foreign import ccall SAFE_CHEAP "gsl_sf_sin" gsl_sf_sin :: Double -> Double
cos_e :: Double -> (Double,Double)
cos_e x = createSFR "cos_e" $ gsl_sf_cos_e x
foreign import ccall SAFE_CHEAP "gsl_sf_cos_e" gsl_sf_cos_e :: Double -> Ptr () -> IO CInt
cos :: Double -> Double
cos = gsl_sf_cos
foreign import ccall SAFE_CHEAP "gsl_sf_cos" gsl_sf_cos :: Double -> Double
hypot_e :: Double -> Double -> (Double,Double)
hypot_e x y = createSFR "hypot_e" $ gsl_sf_hypot_e x y
foreign import ccall SAFE_CHEAP "gsl_sf_hypot_e" gsl_sf_hypot_e :: Double -> Double -> Ptr () -> IO CInt
hypot :: Double -> Double -> Double
hypot = gsl_sf_hypot
foreign import ccall SAFE_CHEAP "gsl_sf_hypot" gsl_sf_hypot :: Double -> Double -> Double
complex_sin_e :: Double -> Double -> ((Double,Double),(Double,Double))
complex_sin_e zr zi = create2SFR "complex_sin_e" $ gsl_sf_complex_sin_e zr zi
foreign import ccall SAFE_CHEAP "gsl_sf_complex_sin_e" gsl_sf_complex_sin_e :: Double -> Double -> Ptr () -> Ptr () -> IO CInt
complex_cos_e :: Double -> Double -> ((Double,Double),(Double,Double))
complex_cos_e zr zi = create2SFR "complex_cos_e" $ gsl_sf_complex_cos_e zr zi
foreign import ccall SAFE_CHEAP "gsl_sf_complex_cos_e" gsl_sf_complex_cos_e :: Double -> Double -> Ptr () -> Ptr () -> IO CInt
complex_logsin_e :: Double -> Double -> ((Double,Double),(Double,Double))
complex_logsin_e zr zi = create2SFR "complex_logsin_e" $ gsl_sf_complex_logsin_e zr zi
foreign import ccall SAFE_CHEAP "gsl_sf_complex_logsin_e" gsl_sf_complex_logsin_e :: Double -> Double -> Ptr () -> Ptr () -> IO CInt
sinc_e :: Double -> (Double,Double)
sinc_e x = createSFR "sinc_e" $ gsl_sf_sinc_e x
foreign import ccall SAFE_CHEAP "gsl_sf_sinc_e" gsl_sf_sinc_e :: Double -> Ptr () -> IO CInt
sinc :: Double -> Double
sinc = gsl_sf_sinc
foreign import ccall SAFE_CHEAP "gsl_sf_sinc" gsl_sf_sinc :: Double -> Double
lnsinh_e :: Double -> (Double,Double)
lnsinh_e x = createSFR "lnsinh_e" $ gsl_sf_lnsinh_e x
foreign import ccall SAFE_CHEAP "gsl_sf_lnsinh_e" gsl_sf_lnsinh_e :: Double -> Ptr () -> IO CInt
lnsinh :: Double -> Double
lnsinh = gsl_sf_lnsinh
foreign import ccall SAFE_CHEAP "gsl_sf_lnsinh" gsl_sf_lnsinh :: Double -> Double
lncosh_e :: Double -> (Double,Double)
lncosh_e x = createSFR "lncosh_e" $ gsl_sf_lncosh_e x
foreign import ccall SAFE_CHEAP "gsl_sf_lncosh_e" gsl_sf_lncosh_e :: Double -> Ptr () -> IO CInt
lncosh :: Double -> Double
lncosh = gsl_sf_lncosh
foreign import ccall SAFE_CHEAP "gsl_sf_lncosh" gsl_sf_lncosh :: Double -> Double
polar_to_rect :: Double -> Double -> ((Double,Double),(Double,Double))
polar_to_rect r theta = create2SFR "polar_to_rect" $ gsl_sf_polar_to_rect r theta
foreign import ccall SAFE_CHEAP "gsl_sf_polar_to_rect" gsl_sf_polar_to_rect :: Double -> Double -> Ptr () -> Ptr () -> IO CInt
rect_to_polar :: Double -> Double -> ((Double,Double),(Double,Double))
rect_to_polar x y = create2SFR "rect_to_polar" $ gsl_sf_rect_to_polar x y
foreign import ccall SAFE_CHEAP "gsl_sf_rect_to_polar" gsl_sf_rect_to_polar :: Double -> Double -> Ptr () -> Ptr () -> IO CInt
sin_err_e :: Double -> Double -> (Double,Double)
sin_err_e x dx = createSFR "sin_err_e" $ gsl_sf_sin_err_e x dx
foreign import ccall SAFE_CHEAP "gsl_sf_sin_err_e" gsl_sf_sin_err_e :: Double -> Double -> Ptr () -> IO CInt
cos_err_e :: Double -> Double -> (Double,Double)
cos_err_e x dx = createSFR "cos_err_e" $ gsl_sf_cos_err_e x dx
foreign import ccall SAFE_CHEAP "gsl_sf_cos_err_e" gsl_sf_cos_err_e :: Double -> Double -> Ptr () -> IO CInt
angle_restrict_symm_e :: Ptr Double -> CInt
angle_restrict_symm_e = gsl_sf_angle_restrict_symm_e
foreign import ccall SAFE_CHEAP "gsl_sf_angle_restrict_symm_e" gsl_sf_angle_restrict_symm_e :: Ptr Double -> CInt
angle_restrict_symm :: Double -> Double
angle_restrict_symm = gsl_sf_angle_restrict_symm
foreign import ccall SAFE_CHEAP "gsl_sf_angle_restrict_symm" gsl_sf_angle_restrict_symm :: Double -> Double
angle_restrict_pos_e :: Ptr Double -> CInt
angle_restrict_pos_e = gsl_sf_angle_restrict_pos_e
foreign import ccall SAFE_CHEAP "gsl_sf_angle_restrict_pos_e" gsl_sf_angle_restrict_pos_e :: Ptr Double -> CInt
angle_restrict_pos :: Double -> Double
angle_restrict_pos = gsl_sf_angle_restrict_pos
foreign import ccall SAFE_CHEAP "gsl_sf_angle_restrict_pos" gsl_sf_angle_restrict_pos :: Double -> Double
angle_restrict_symm_err_e :: Double -> (Double,Double)
angle_restrict_symm_err_e theta = createSFR "angle_restrict_symm_err_e" $ gsl_sf_angle_restrict_symm_err_e theta
foreign import ccall SAFE_CHEAP "gsl_sf_angle_restrict_symm_err_e" gsl_sf_angle_restrict_symm_err_e :: Double -> Ptr () -> IO CInt
angle_restrict_pos_err_e :: Double -> (Double,Double)
angle_restrict_pos_err_e theta = createSFR "angle_restrict_pos_err_e" $ gsl_sf_angle_restrict_pos_err_e theta
foreign import ccall SAFE_CHEAP "gsl_sf_angle_restrict_pos_err_e" gsl_sf_angle_restrict_pos_err_e :: Double -> Ptr () -> IO CInt