Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
- Floating-point wrappers of Arb mathematical functions
- Option and return flags
- Elementary functions
- Gamma, zeta and related functions
- Error functions and exponential integrals
- Bessel, Airy and Coulomb functions
- Orthogonal polynomials
- Hypergeometric functions
- Elliptic integrals, elliptic functions and modular forms
Warning: This module is experimental (as of Arb 2.21). It has not been extensively tested, and interfaces may change in the future.
This module provides wrappers of Arb functions intended users who want accurate floating-point mathematical functions without necessarily caring about ball arithmetic. The wrappers take floating-point input, give floating-point output, and automatically increase the internal working precision to ensure that the output is accurate (in the rare case of failure, they output NaN along with an error code).
Outputs are passed by reference so that we can return status flags and so that the interface is uniform for functions with multiple outputs.
The Haskell version of the c-functions require Ptr for the complex values. The functions can be wrapped to a regular Haskell function
Example
import System.IO.Unsafe import Foreign.Ptr import Foreign.C.Types import Data.Number.Flint.Arb.FpWrap main = do print $ airy_ai 1 print $ airy_ai' 1 airy_ai = liftD arb_fpwrap_double_airy_ai airy_ai' = liftD arb_fpwrap_double_airy_ai_prime liftD :: (Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn) -> (Double -> Double) liftD f x = unsafePerformIO $ do r <- malloc :: IO (Ptr CDouble) flag <- f r (realToFrac x) 0 res <- peek r free r return $ realToFrac res
Running main yields:
>>>
main
produces the output
0.13529241631288141 -0.1591474412967932
Synopsis
- newtype FpWrapReturn = FpWrapReturn {}
- fpwrap_success :: FpWrapReturn
- fpwrap_unable :: FpWrapReturn
- fpwrap_accurate_parts :: FpWrapReturn
- fpwrap_correct_rounding :: FpWrapReturn
- fpwrap_work_limit :: FpWrapReturn
- arb_fpwrap_double_exp :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_exp :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_expm1 :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_expm1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_log :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_log :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_log1p :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_log1p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_pow :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_pow :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sqrt :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sqrt :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_rsqrt :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_rsqrt :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_cbrt :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_cbrt :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sin :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sin :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_cos :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_cos :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_tan :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_tan :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_cot :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_cot :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sec :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sec :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_csc :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_csc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sinc :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sinc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sin_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sin_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_cos_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_cos_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_tan_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_tan_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_cot_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_cot_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sinc_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sinc_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_asin :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_asin :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_acos :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_acos :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_atan :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_atan :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_atan2 :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_asinh :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_asinh :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_acosh :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_acosh :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_atanh :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_atanh :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_lambertw :: Ptr CDouble -> CDouble -> CLong -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_lambertw :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CLong -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_rising :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_rising :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_gamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_gamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_rgamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_rgamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_lgamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_lgamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_digamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_digamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_zeta :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_zeta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_hurwitz_zeta :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hurwitz_zeta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_lerch_phi :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_lerch_phi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_barnes_g :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_barnes_g :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_log_barnes_g :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_log_barnes_g :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_polygamma :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_polygamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_polylog :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_polylog :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_dirichlet_eta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_riemann_xi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hardy_theta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hardy_z :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_zeta_zero :: Ptr (Complex CDouble) -> CULong -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_erf :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_erf :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_erfc :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_erfc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_erfi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_erfi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_erfinv :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_erfcinv :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_fresnel_s :: Ptr CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_fresnel_s :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_fresnel_c :: Ptr CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_fresnel_c :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_gamma_upper :: Ptr CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_gamma_upper :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_gamma_lower :: Ptr CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_gamma_lower :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_beta_lower :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_beta_lower :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_exp_integral_e :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_exp_integral_e :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_exp_integral_ei :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_exp_integral_ei :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sin_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sin_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_cos_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_cos_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_sinh_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_sinh_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_cosh_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_cosh_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_log_integral :: Ptr CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_log_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_dilog :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_dilog :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_bessel_j :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_bessel_j :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_bessel_y :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_bessel_y :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_bessel_i :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_bessel_i :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_bessel_k :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_bessel_k :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_bessel_k_scaled :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_bessel_k_scaled :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_ai :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_airy_ai :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_ai_prime :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_airy_ai_prime :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_bi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_airy_bi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_bi_prime :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_airy_bi_prime :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_ai_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_ai_prime_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_bi_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_airy_bi_prime_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_coulomb_f :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_coulomb_f :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_coulomb_g :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_coulomb_g :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_coulomb_hpos :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_coulomb_hneg :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_chebyshev_t :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_chebyshev_t :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_chebyshev_u :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_chebyshev_u :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_jacobi_p :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_jacobi_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_gegenbauer_c :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_gegenbauer_c :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_laguerre_l :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_laguerre_l :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_hermite_h :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hermite_h :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_legendre_p :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_legendre_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_legendre_q :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_legendre_q :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_legendre_root :: Ptr CDouble -> Ptr CDouble -> CULong -> CULong -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_spherical_y :: Ptr (Complex CDouble) -> CLong -> CLong -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_hypgeom_0f1 :: Ptr CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hypgeom_0f1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_hypgeom_1f1 :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hypgeom_1f1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_hypgeom_u :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hypgeom_u :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_hypgeom_2f1 :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hypgeom_2f1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_hypgeom_pfq :: Ptr CDouble -> Ptr CDouble -> CLong -> Ptr CDouble -> CLong -> CDouble -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_hypgeom_pfq :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CLong -> Ptr (Complex CDouble) -> CLong -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_double_agm :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_agm :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_k :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_e :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_f :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_e_inc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_pi_inc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_rf :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_rg :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_rj :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_p_prime :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_inv_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_zeta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_elliptic_sigma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_jacobi_theta_1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_jacobi_theta_2 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_jacobi_theta_3 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_jacobi_theta_4 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_dedekind_eta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_modular_j :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_modular_lambda :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
- arb_fpwrap_cdouble_modular_delta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn
Floating-point wrappers of Arb mathematical functions
Option and return flags
newtype FpWrapReturn Source #
Return type for fpwrap functions
Instances
Show FpWrapReturn Source # | |
Defined in Data.Number.Flint.Arb.FpWrap.FFI showsPrec :: Int -> FpWrapReturn -> ShowS # show :: FpWrapReturn -> String # showList :: [FpWrapReturn] -> ShowS # | |
Eq FpWrapReturn Source # | |
Defined in Data.Number.Flint.Arb.FpWrap.FFI (==) :: FpWrapReturn -> FpWrapReturn -> Bool # (/=) :: FpWrapReturn -> FpWrapReturn -> Bool # |
fpwrap_success :: FpWrapReturn Source #
Indicates an accurate result. (Up to inevitable underflow or overflow in the final conversion to a floating-point result; see above.)
This flag has the numerical value 0.
fpwrap_unable :: FpWrapReturn Source #
Indicates failure (unable to achieve to target accuracy, possibly because of a singularity). The output is set to NaN.
This flag has the numerical value 1. Functions take a flags parameter specifying optional rounding and termination behavior. This can be set to 0 to use defaults.
fpwrap_accurate_parts :: FpWrapReturn Source #
For complex output, compute both real and imaginary parts to full relative accuracy. By default (if this flag is not set), complex results are computed to at least 53-bit accuracy as a whole, but if either the real or imaginary part is much smaller than the other, that part can have a large relative error. Setting this flag can result in slower evaluation or failure to converge in some cases.
This flag has the numerical value 1.
fpwrap_correct_rounding :: FpWrapReturn Source #
Guarantees correct rounding. By default (if this flag is not set), real results are accurate up to the rounding of the last bit, but the last bit is not guaranteed to be rounded optimally. Setting this flag can result in slower evaluation or failure to converge in some cases. Correct rounding automatically applies to both real and imaginary parts of complex numbers, so it is unnecessary to set both this flag and FPWRAP_ACCURATE_PARTS.
This flag has the numerical value 2.
fpwrap_work_limit :: FpWrapReturn Source #
Multiplied by an integer, specifies the maximum working precision to use before giving up. With n * FPWRAP_WORK_LIMIT added to flags, levels of precision will be used. The default is equivalent to , which for double means trying with a working precision of 64, 128, 256, 512, 1024, 2048, 4096, 8192 bits. With flags = 2 * FPWRAP_WORK_LIMIT, we only try 64 and 128 bits, and with flags = 16 * FPWRAP_WORK_LIMIT we go up to 2097152 bits.
This flag has the numerical value 65536.
Elementary functions
arb_fpwrap_double_exp :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_exp res x flags
arb_fpwrap_cdouble_exp :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_exp res x flags
arb_fpwrap_double_expm1 :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_expm1 res x flags
arb_fpwrap_cdouble_expm1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_expm1 res x flags
arb_fpwrap_double_log :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_log res x flags
arb_fpwrap_cdouble_log :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_log res x flags
arb_fpwrap_double_log1p :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_log1p res x flags
arb_fpwrap_cdouble_log1p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_log1p res x flags
arb_fpwrap_double_pow :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_pow res x y flags
arb_fpwrap_cdouble_pow :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_pow res x y flags
arb_fpwrap_double_sqrt :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sqrt res x flags
arb_fpwrap_cdouble_sqrt :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sqrt res x flags
arb_fpwrap_double_rsqrt :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_rsqrt res x flags
arb_fpwrap_cdouble_rsqrt :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_rsqrt res x flags
arb_fpwrap_double_cbrt :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_cbrt res x flags
arb_fpwrap_cdouble_cbrt :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_cbrt res x flags
arb_fpwrap_double_sin :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sin res x flags
arb_fpwrap_cdouble_sin :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sin res x flags
arb_fpwrap_double_cos :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_cos res x flags
arb_fpwrap_cdouble_cos :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_cos res x flags
arb_fpwrap_double_tan :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_tan res x flags
arb_fpwrap_cdouble_tan :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_tan res x flags
arb_fpwrap_double_cot :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_cot res x flags
arb_fpwrap_cdouble_cot :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_cot res x flags
arb_fpwrap_double_sec :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sec res x flags
arb_fpwrap_cdouble_sec :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sec res x flags
arb_fpwrap_double_csc :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_csc res x flags
arb_fpwrap_cdouble_csc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_csc res x flags
arb_fpwrap_double_sinc :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sinc res x flags
arb_fpwrap_cdouble_sinc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sinc res x flags
arb_fpwrap_double_sin_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sin_pi res x flags
arb_fpwrap_cdouble_sin_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sin_pi res x flags
arb_fpwrap_double_cos_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_cos_pi res x flags
arb_fpwrap_cdouble_cos_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_cos_pi res x flags
arb_fpwrap_double_tan_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_tan_pi res x flags
arb_fpwrap_cdouble_tan_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_tan_pi res x flags
arb_fpwrap_double_cot_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_cot_pi res x flags
arb_fpwrap_cdouble_cot_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_cot_pi res x flags
arb_fpwrap_double_sinc_pi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sinc_pi res x flags
arb_fpwrap_cdouble_sinc_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sinc_pi res x flags
arb_fpwrap_double_asin :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_asin res x flags
arb_fpwrap_cdouble_asin :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_asin res x flags
arb_fpwrap_double_acos :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_acos res x flags
arb_fpwrap_cdouble_acos :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_acos res x flags
arb_fpwrap_double_atan :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_atan res x flags
arb_fpwrap_cdouble_atan :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_atan res x flags
arb_fpwrap_double_atan2 :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_atan2 res x1 x2 flags
arb_fpwrap_double_asinh :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_asinh res x flags
arb_fpwrap_cdouble_asinh :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_asinh res x flags
arb_fpwrap_double_acosh :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_acosh res x flags
arb_fpwrap_cdouble_acosh :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_acosh res x flags
arb_fpwrap_double_atanh :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_atanh res x flags
arb_fpwrap_cdouble_atanh :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_atanh res x flags
arb_fpwrap_double_lambertw :: Ptr CDouble -> CDouble -> CLong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_lambertw res x branch flags
arb_fpwrap_cdouble_lambertw :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CLong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_lambertw res x branch flags
Gamma, zeta and related functions
arb_fpwrap_double_rising :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_rising res x n flags
arb_fpwrap_cdouble_rising :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_rising res x n flags
Rising factorial.
arb_fpwrap_double_gamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_gamma res x flags
arb_fpwrap_cdouble_gamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_gamma res x flags
Gamma function.
arb_fpwrap_double_rgamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_rgamma res x flags
arb_fpwrap_cdouble_rgamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_rgamma res x flags
Reciprocal gamma function.
arb_fpwrap_double_lgamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_lgamma res x flags
arb_fpwrap_cdouble_lgamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_lgamma res x flags
Log-gamma function.
arb_fpwrap_double_digamma :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_digamma res x flags
arb_fpwrap_cdouble_digamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_digamma res x flags
Digamma function.
arb_fpwrap_double_zeta :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_zeta res x flags
arb_fpwrap_cdouble_zeta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_zeta res x flags
Riemann zeta function.
arb_fpwrap_double_hurwitz_zeta :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_hurwitz_zeta res s z flags
arb_fpwrap_cdouble_hurwitz_zeta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hurwitz_zeta res s z flags
Hurwitz zeta function.
arb_fpwrap_double_lerch_phi :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_lerch_phi res z s a flags
arb_fpwrap_cdouble_lerch_phi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_lerch_phi res z s a flags
Lerch transcendent.
arb_fpwrap_double_barnes_g :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_barnes_g res x flags
arb_fpwrap_cdouble_barnes_g :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_barnes_g res x flags
Barnes G-function.
arb_fpwrap_double_log_barnes_g :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_log_barnes_g res x flags
arb_fpwrap_cdouble_log_barnes_g :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_log_barnes_g res x flags
Logarithmic Barnes G-function.
arb_fpwrap_double_polygamma :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_polygamma res s z flags
arb_fpwrap_cdouble_polygamma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_polygamma res s z flags
Polygamma function.
arb_fpwrap_double_polylog :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_polylog res s z flags
arb_fpwrap_cdouble_polylog :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_polylog res s z flags
Polylogarithm.
arb_fpwrap_cdouble_dirichlet_eta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_dirichlet_eta res s flags
arb_fpwrap_cdouble_riemann_xi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_riemann_xi res s flags
arb_fpwrap_cdouble_hardy_theta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hardy_theta res z flags
arb_fpwrap_cdouble_hardy_z :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hardy_z res z flags
arb_fpwrap_cdouble_zeta_zero :: Ptr (Complex CDouble) -> CULong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_zeta_zero res n flags
Error functions and exponential integrals
arb_fpwrap_double_erf :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_erf res x flags
arb_fpwrap_cdouble_erf :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_erf res x flags
arb_fpwrap_double_erfc :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_erfc res x flags
arb_fpwrap_cdouble_erfc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_erfc res x flags
arb_fpwrap_double_erfi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_erfi res x flags
arb_fpwrap_cdouble_erfi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_erfi res x flags
arb_fpwrap_double_erfinv :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_erfinv res x flags
arb_fpwrap_double_erfcinv :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_erfcinv res x flags
arb_fpwrap_double_fresnel_s :: Ptr CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_fresnel_s res x normalized flags
arb_fpwrap_cdouble_fresnel_s :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_fresnel_s res x normalized flags
arb_fpwrap_double_fresnel_c :: Ptr CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_fresnel_c res x normalized flags
arb_fpwrap_cdouble_fresnel_c :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_fresnel_c res x normalized flags
arb_fpwrap_double_gamma_upper :: Ptr CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_gamma_upper res s z regularized flags
arb_fpwrap_cdouble_gamma_upper :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_gamma_upper res s z regularized flags
arb_fpwrap_double_gamma_lower :: Ptr CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_gamma_lower res s z regularized flags
arb_fpwrap_cdouble_gamma_lower :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_gamma_lower res s z regularized flags
arb_fpwrap_double_beta_lower :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_beta_lower res a b z regularized flags
arb_fpwrap_cdouble_beta_lower :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_beta_lower res a b z regularized flags
arb_fpwrap_double_exp_integral_e :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_exp_integral_e res s z flags
arb_fpwrap_cdouble_exp_integral_e :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_exp_integral_e res s z flags
arb_fpwrap_double_exp_integral_ei :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_exp_integral_ei res x flags
arb_fpwrap_cdouble_exp_integral_ei :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_exp_integral_ei res x flags
arb_fpwrap_double_sin_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sin_integral res x flags
arb_fpwrap_cdouble_sin_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sin_integral res x flags
arb_fpwrap_double_cos_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_cos_integral res x flags
arb_fpwrap_cdouble_cos_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_cos_integral res x flags
arb_fpwrap_double_sinh_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_sinh_integral res x flags
arb_fpwrap_cdouble_sinh_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_sinh_integral res x flags
arb_fpwrap_double_cosh_integral :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_cosh_integral res x flags
arb_fpwrap_cdouble_cosh_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_cosh_integral res x flags
arb_fpwrap_double_log_integral :: Ptr CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_log_integral res x offset flags
arb_fpwrap_cdouble_log_integral :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_log_integral res x offset flags
arb_fpwrap_double_dilog :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_dilog res x flags
arb_fpwrap_cdouble_dilog :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_dilog res x flags
Bessel, Airy and Coulomb functions
arb_fpwrap_double_bessel_j :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_bessel_j res nu x flags
arb_fpwrap_cdouble_bessel_j :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_bessel_j res nu x flags
arb_fpwrap_double_bessel_y :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_bessel_y res nu x flags
arb_fpwrap_cdouble_bessel_y :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_bessel_y res nu x flags
arb_fpwrap_double_bessel_i :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_bessel_i res nu x flags
arb_fpwrap_cdouble_bessel_i :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_bessel_i res nu x flags
arb_fpwrap_double_bessel_k :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_bessel_k res nu x flags
arb_fpwrap_cdouble_bessel_k :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_bessel_k res nu x flags
arb_fpwrap_double_bessel_k_scaled :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_bessel_k_scaled res nu x flags
arb_fpwrap_cdouble_bessel_k_scaled :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_bessel_k_scaled res nu x flags
arb_fpwrap_double_airy_ai :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_ai res x flags
arb_fpwrap_cdouble_airy_ai :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_airy_ai res x flags
arb_fpwrap_double_airy_ai_prime :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_ai_prime res x flags
arb_fpwrap_cdouble_airy_ai_prime :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_airy_ai_prime res x flags
arb_fpwrap_double_airy_bi :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_bi res x flags
arb_fpwrap_cdouble_airy_bi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_airy_bi res x flags
arb_fpwrap_double_airy_bi_prime :: Ptr CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_bi_prime res x flags
arb_fpwrap_cdouble_airy_bi_prime :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_airy_bi_prime res x flags
arb_fpwrap_double_airy_ai_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_ai_zero res n flags
arb_fpwrap_double_airy_ai_prime_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_ai_prime_zero res n flags
arb_fpwrap_double_airy_bi_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_bi_zero res n flags
arb_fpwrap_double_airy_bi_prime_zero :: Ptr CDouble -> CULong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_airy_bi_prime_zero res n flags
arb_fpwrap_double_coulomb_f :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_coulomb_f res l eta x flags
arb_fpwrap_cdouble_coulomb_f :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_coulomb_f res l eta x flags
arb_fpwrap_double_coulomb_g :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_coulomb_g res l eta x flags
arb_fpwrap_cdouble_coulomb_g :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_coulomb_g res l eta x flags
arb_fpwrap_cdouble_coulomb_hpos :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_coulomb_hpos res l eta x flags
arb_fpwrap_cdouble_coulomb_hneg :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_coulomb_hneg res l eta x flags
Orthogonal polynomials
arb_fpwrap_double_chebyshev_t :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_chebyshev_t res n x flags
arb_fpwrap_cdouble_chebyshev_t :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_chebyshev_t res n x flags
arb_fpwrap_double_chebyshev_u :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_chebyshev_u res n x flags
arb_fpwrap_cdouble_chebyshev_u :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_chebyshev_u res n x flags
arb_fpwrap_double_jacobi_p :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_jacobi_p res n a b x flags
arb_fpwrap_cdouble_jacobi_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_jacobi_p res n a b x flags
arb_fpwrap_double_gegenbauer_c :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_gegenbauer_c res n m x flags
arb_fpwrap_cdouble_gegenbauer_c :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_gegenbauer_c res n m x flags
arb_fpwrap_double_laguerre_l :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_laguerre_l res n m x flags
arb_fpwrap_cdouble_laguerre_l :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_laguerre_l res n m x flags
arb_fpwrap_double_hermite_h :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_hermite_h res n x flags
arb_fpwrap_cdouble_hermite_h :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hermite_h res n x flags
arb_fpwrap_double_legendre_p :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_legendre_p res n m x type flags
arb_fpwrap_cdouble_legendre_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_legendre_p res n m x type flags
arb_fpwrap_double_legendre_q :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_legendre_q res n m x type flags
arb_fpwrap_cdouble_legendre_q :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_legendre_q res n m x type flags
arb_fpwrap_double_legendre_root :: Ptr CDouble -> Ptr CDouble -> CULong -> CULong -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_legendre_root res1 res2 n k flags
Sets res1 to the index k root of the Legendre polynomial \(P_n(x)\), and simultaneously sets res2 to the corresponding weight for Gauss-Legendre quadrature.
arb_fpwrap_cdouble_spherical_y :: Ptr (Complex CDouble) -> CLong -> CLong -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_spherical_y res n m x1 x2 flags
Hypergeometric functions
arb_fpwrap_double_hypgeom_0f1 :: Ptr CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_hypgeom_0f1 res a x regularized flags
arb_fpwrap_cdouble_hypgeom_0f1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hypgeom_0f1 res a x regularized flags
arb_fpwrap_double_hypgeom_1f1 :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_hypgeom_1f1 res a b x regularized flags
arb_fpwrap_cdouble_hypgeom_1f1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hypgeom_1f1 res a b x regularized flags
arb_fpwrap_double_hypgeom_u :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_hypgeom_u res a b x flags
arb_fpwrap_cdouble_hypgeom_u :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hypgeom_u res a b x flags
arb_fpwrap_double_hypgeom_2f1 :: Ptr CDouble -> CDouble -> CDouble -> CDouble -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_hypgeom_2f1 res a b c x regularized flags
arb_fpwrap_cdouble_hypgeom_2f1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hypgeom_2f1 res a b c x regularized flags
arb_fpwrap_double_hypgeom_pfq :: Ptr CDouble -> Ptr CDouble -> CLong -> Ptr CDouble -> CLong -> CDouble -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_hypgeom_pfq res a p b q z regularized flags
arb_fpwrap_cdouble_hypgeom_pfq :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CLong -> Ptr (Complex CDouble) -> CLong -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_hypgeom_pfq res a p b q z regularized flags
Elliptic integrals, elliptic functions and modular forms
arb_fpwrap_double_agm :: Ptr CDouble -> CDouble -> CDouble -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_double_agm res x y flags
arb_fpwrap_cdouble_agm :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_agm res x y flags
Arithmetic-geometric mean.
arb_fpwrap_cdouble_elliptic_k :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_k res m flags
arb_fpwrap_cdouble_elliptic_e :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_e res m flags
arb_fpwrap_cdouble_elliptic_pi :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_pi res n m flags
arb_fpwrap_cdouble_elliptic_f :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_f res phi m pi flags
arb_fpwrap_cdouble_elliptic_e_inc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_e_inc res phi m pi flags
arb_fpwrap_cdouble_elliptic_pi_inc :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_pi_inc res n phi m pi flags
Complete and incomplete elliptic integrals.
arb_fpwrap_cdouble_elliptic_rf :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_rf res x y z option flags
arb_fpwrap_cdouble_elliptic_rg :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_rg res x y z option flags
arb_fpwrap_cdouble_elliptic_rj :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_rj res x y z w option flags
Carlson symmetric elliptic integrals.
arb_fpwrap_cdouble_elliptic_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_p res z tau flags
arb_fpwrap_cdouble_elliptic_p_prime :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_p_prime res z tau flags
arb_fpwrap_cdouble_elliptic_inv_p :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_inv_p res z tau flags
arb_fpwrap_cdouble_elliptic_zeta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_zeta res z tau flags
arb_fpwrap_cdouble_elliptic_sigma :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_elliptic_sigma res z tau flags
Weierstrass elliptic functions.
arb_fpwrap_cdouble_jacobi_theta_1 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_jacobi_theta_1 res z tau flags
arb_fpwrap_cdouble_jacobi_theta_2 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_jacobi_theta_2 res z tau flags
arb_fpwrap_cdouble_jacobi_theta_3 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_jacobi_theta_3 res z tau flags
arb_fpwrap_cdouble_jacobi_theta_4 :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_jacobi_theta_4 res z tau flags
Jacobi theta functions.
arb_fpwrap_cdouble_dedekind_eta :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_dedekind_eta res tau flags
arb_fpwrap_cdouble_modular_j :: Ptr (Complex CDouble) -> Ptr (Complex CDouble) -> CInt -> IO FpWrapReturn Source #
arb_fpwrap_cdouble_modular_j res tau flags