{-# INCLUDE <bindings.macros.h> #-}
{-# INCLUDE <math.h> #-}
{-# LINE 1 "src/Bindings/C/Math.hsc" #-}

{-# LINE 2 "src/Bindings/C/Math.hsc" #-}

{-# LINE 3 "src/Bindings/C/Math.hsc" #-}

-- | <http://www.opengroup.org/onlinepubs/9699919799/basedefs/math.h.html>

module Bindings.C.Math where
import Foreign
import Foreign.C

c'FP_INFINITE = 1
c'FP_INFINITE :: (Num a) => a

{-# LINE 11 "src/Bindings/C/Math.hsc" #-}
c'FP_NAN = 0
c'FP_NAN :: (Num a) => a

{-# LINE 12 "src/Bindings/C/Math.hsc" #-}
c'FP_NORMAL = 4
c'FP_NORMAL :: (Num a) => a

{-# LINE 13 "src/Bindings/C/Math.hsc" #-}
c'FP_SUBNORMAL = 3
c'FP_SUBNORMAL :: (Num a) => a

{-# LINE 14 "src/Bindings/C/Math.hsc" #-}
c'FP_ZERO = 2
c'FP_ZERO :: (Num a) => a

{-# LINE 15 "src/Bindings/C/Math.hsc" #-}
c'FP_ILOGB0 = -2147483648
c'FP_ILOGB0 :: (Num a) => a

{-# LINE 16 "src/Bindings/C/Math.hsc" #-}
c'FP_ILOGBNAN = -2147483648
c'FP_ILOGBNAN :: (Num a) => a

{-# LINE 17 "src/Bindings/C/Math.hsc" #-}
c'MATH_ERRNO = 1
c'MATH_ERRNO :: (Num a) => a

{-# LINE 18 "src/Bindings/C/Math.hsc" #-}
c'MATH_ERREXCEPT = 2
c'MATH_ERREXCEPT :: (Num a) => a

{-# LINE 19 "src/Bindings/C/Math.hsc" #-}

foreign import ccall "acos" c'acos
  :: CDouble -> IO CDouble
foreign import ccall "&acos" p'acos
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 21 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "acosf" c'acosf
  :: CFloat -> IO CFloat
foreign import ccall "&acosf" p'acosf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 22 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "acosh" c'acosh
  :: CDouble -> IO CDouble
foreign import ccall "&acosh" p'acosh
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 23 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "acoshf" c'acoshf
  :: CFloat -> IO CFloat
foreign import ccall "&acoshf" p'acoshf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 24 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "acoshl" c'acoshl
  :: CLDouble -> IO CLDouble
foreign import ccall "&acoshl" p'acoshl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 25 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "acosl" c'acosl
  :: CLDouble -> IO CLDouble
foreign import ccall "&acosl" p'acosl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 26 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "asin" c'asin
  :: CDouble -> IO CDouble
foreign import ccall "&asin" p'asin
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 27 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "asinf" c'asinf
  :: CFloat -> IO CFloat
foreign import ccall "&asinf" p'asinf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 28 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "asinh" c'asinh
  :: CDouble -> IO CDouble
foreign import ccall "&asinh" p'asinh
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 29 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "asinhf" c'asinhf
  :: CFloat -> IO CFloat
foreign import ccall "&asinhf" p'asinhf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 30 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "asinhl" c'asinhl
  :: CLDouble -> IO CLDouble
foreign import ccall "&asinhl" p'asinhl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 31 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "asinl" c'asinl
  :: CLDouble -> IO CLDouble
foreign import ccall "&asinl" p'asinl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 32 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atan" c'atan
  :: CDouble -> IO CDouble
foreign import ccall "&atan" p'atan
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 33 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atan2" c'atan2
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&atan2" p'atan2
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 34 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atan2f" c'atan2f
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&atan2f" p'atan2f
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 35 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atan2l" c'atan2l
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&atan2l" p'atan2l
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 36 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atanf" c'atanf
  :: CFloat -> IO CFloat
foreign import ccall "&atanf" p'atanf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 37 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atanh" c'atanh
  :: CDouble -> IO CDouble
foreign import ccall "&atanh" p'atanh
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 38 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atanhf" c'atanhf
  :: CFloat -> IO CFloat
foreign import ccall "&atanhf" p'atanhf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 39 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atanhl" c'atanhl
  :: CLDouble -> IO CLDouble
foreign import ccall "&atanhl" p'atanhl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 40 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "atanl" c'atanl
  :: CLDouble -> IO CLDouble
foreign import ccall "&atanl" p'atanl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 41 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "cbrt" c'cbrt
  :: CDouble -> IO CDouble
foreign import ccall "&cbrt" p'cbrt
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 42 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "cbrtf" c'cbrtf
  :: CFloat -> IO CFloat
foreign import ccall "&cbrtf" p'cbrtf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 43 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "cbrtl" c'cbrtl
  :: CLDouble -> IO CLDouble
foreign import ccall "&cbrtl" p'cbrtl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 44 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ceil" c'ceil
  :: CDouble -> IO CDouble
foreign import ccall "&ceil" p'ceil
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 45 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ceilf" c'ceilf
  :: CFloat -> IO CFloat
foreign import ccall "&ceilf" p'ceilf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 46 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ceill" c'ceill
  :: CLDouble -> IO CLDouble
foreign import ccall "&ceill" p'ceill
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 47 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "copysign" c'copysign
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&copysign" p'copysign
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 48 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "copysignf" c'copysignf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&copysignf" p'copysignf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 49 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "copysignl" c'copysignl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&copysignl" p'copysignl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 50 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "cos" c'cos
  :: CDouble -> IO CDouble
foreign import ccall "&cos" p'cos
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 51 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "cosf" c'cosf
  :: CFloat -> IO CFloat
foreign import ccall "&cosf" p'cosf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 52 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "cosh" c'cosh
  :: CDouble -> IO CDouble
foreign import ccall "&cosh" p'cosh
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 53 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "coshf" c'coshf
  :: CFloat -> IO CFloat
foreign import ccall "&coshf" p'coshf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 54 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "coshl" c'coshl
  :: CLDouble -> IO CLDouble
foreign import ccall "&coshl" p'coshl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 55 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "cosl" c'cosl
  :: CLDouble -> IO CLDouble
foreign import ccall "&cosl" p'cosl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 56 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "erf" c'erf
  :: CDouble -> IO CDouble
foreign import ccall "&erf" p'erf
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 57 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "erfc" c'erfc
  :: CDouble -> IO CDouble
foreign import ccall "&erfc" p'erfc
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 58 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "erfcf" c'erfcf
  :: CFloat -> IO CFloat
foreign import ccall "&erfcf" p'erfcf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 59 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "erfcl" c'erfcl
  :: CLDouble -> IO CLDouble
foreign import ccall "&erfcl" p'erfcl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 60 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "erff" c'erff
  :: CFloat -> IO CFloat
foreign import ccall "&erff" p'erff
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 61 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "erfl" c'erfl
  :: CLDouble -> IO CLDouble
foreign import ccall "&erfl" p'erfl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 62 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "exp" c'exp
  :: CDouble -> IO CDouble
foreign import ccall "&exp" p'exp
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 63 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "exp2" c'exp2
  :: CDouble -> IO CDouble
foreign import ccall "&exp2" p'exp2
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 64 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "exp2f" c'exp2f
  :: CFloat -> IO CFloat
foreign import ccall "&exp2f" p'exp2f
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 65 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "exp2l" c'exp2l
  :: CLDouble -> IO CLDouble
foreign import ccall "&exp2l" p'exp2l
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 66 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "expf" c'expf
  :: CFloat -> IO CFloat
foreign import ccall "&expf" p'expf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 67 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "expl" c'expl
  :: CLDouble -> IO CLDouble
foreign import ccall "&expl" p'expl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 68 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "expm1" c'expm1
  :: CDouble -> IO CDouble
foreign import ccall "&expm1" p'expm1
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 69 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "expm1f" c'expm1f
  :: CFloat -> IO CFloat
foreign import ccall "&expm1f" p'expm1f
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 70 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "expm1l" c'expm1l
  :: CLDouble -> IO CLDouble
foreign import ccall "&expm1l" p'expm1l
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 71 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fabs" c'fabs
  :: CDouble -> IO CDouble
foreign import ccall "&fabs" p'fabs
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 72 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fabsf" c'fabsf
  :: CFloat -> IO CFloat
foreign import ccall "&fabsf" p'fabsf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 73 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fabsl" c'fabsl
  :: CLDouble -> IO CLDouble
foreign import ccall "&fabsl" p'fabsl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 74 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fdim" c'fdim
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&fdim" p'fdim
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 75 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fdimf" c'fdimf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&fdimf" p'fdimf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 76 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fdiml" c'fdiml
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&fdiml" p'fdiml
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 77 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "floor" c'floor
  :: CDouble -> IO CDouble
foreign import ccall "&floor" p'floor
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 78 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "floorf" c'floorf
  :: CFloat -> IO CFloat
foreign import ccall "&floorf" p'floorf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 79 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "floorl" c'floorl
  :: CLDouble -> IO CLDouble
foreign import ccall "&floorl" p'floorl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 80 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fma" c'fma
  :: CDouble -> CDouble -> CDouble -> IO CDouble
foreign import ccall "&fma" p'fma
  :: FunPtr (CDouble -> CDouble -> CDouble -> IO CDouble)

{-# LINE 81 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmaf" c'fmaf
  :: CFloat -> CFloat -> CFloat -> IO CFloat
foreign import ccall "&fmaf" p'fmaf
  :: FunPtr (CFloat -> CFloat -> CFloat -> IO CFloat)

{-# LINE 82 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmal" c'fmal
  :: CLDouble -> CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&fmal" p'fmal
  :: FunPtr (CLDouble -> CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 83 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmax" c'fmax
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&fmax" p'fmax
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 84 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmaxf" c'fmaxf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&fmaxf" p'fmaxf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 85 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmaxl" c'fmaxl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&fmaxl" p'fmaxl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 86 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmin" c'fmin
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&fmin" p'fmin
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 87 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fminf" c'fminf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&fminf" p'fminf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 88 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fminl" c'fminl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&fminl" p'fminl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 89 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmod" c'fmod
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&fmod" p'fmod
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 90 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmodf" c'fmodf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&fmodf" p'fmodf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 91 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "fmodl" c'fmodl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&fmodl" p'fmodl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 92 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "frexp" c'frexp
  :: CDouble -> Ptr CInt -> IO CDouble
foreign import ccall "&frexp" p'frexp
  :: FunPtr (CDouble -> Ptr CInt -> IO CDouble)

{-# LINE 93 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "frexpf" c'frexpf
  :: CFloat -> Ptr CInt -> IO CFloat
foreign import ccall "&frexpf" p'frexpf
  :: FunPtr (CFloat -> Ptr CInt -> IO CFloat)

{-# LINE 94 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "frexpl" c'frexpl
  :: CLDouble -> Ptr CInt -> IO CLDouble
foreign import ccall "&frexpl" p'frexpl
  :: FunPtr (CLDouble -> Ptr CInt -> IO CLDouble)

{-# LINE 95 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "hypot" c'hypot
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&hypot" p'hypot
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 96 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "hypotf" c'hypotf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&hypotf" p'hypotf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 97 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "hypotl" c'hypotl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&hypotl" p'hypotl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 98 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ilogb" c'ilogb
  :: CDouble -> IO CInt
foreign import ccall "&ilogb" p'ilogb
  :: FunPtr (CDouble -> IO CInt)

{-# LINE 99 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ilogbf" c'ilogbf
  :: CFloat -> IO CInt
foreign import ccall "&ilogbf" p'ilogbf
  :: FunPtr (CFloat -> IO CInt)

{-# LINE 100 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ilogbl" c'ilogbl
  :: CLDouble -> IO CInt
foreign import ccall "&ilogbl" p'ilogbl
  :: FunPtr (CLDouble -> IO CInt)

{-# LINE 101 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ldexp" c'ldexp
  :: CDouble -> CInt -> IO CDouble
foreign import ccall "&ldexp" p'ldexp
  :: FunPtr (CDouble -> CInt -> IO CDouble)

{-# LINE 102 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ldexpf" c'ldexpf
  :: CFloat -> CInt -> IO CFloat
foreign import ccall "&ldexpf" p'ldexpf
  :: FunPtr (CFloat -> CInt -> IO CFloat)

{-# LINE 103 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "ldexpl" c'ldexpl
  :: CLDouble -> CInt -> IO CLDouble
foreign import ccall "&ldexpl" p'ldexpl
  :: FunPtr (CLDouble -> CInt -> IO CLDouble)

{-# LINE 104 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lgamma" c'lgamma
  :: CDouble -> IO CDouble
foreign import ccall "&lgamma" p'lgamma
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 105 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lgammaf" c'lgammaf
  :: CFloat -> IO CFloat
foreign import ccall "&lgammaf" p'lgammaf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 106 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lgammal" c'lgammal
  :: CLDouble -> IO CLDouble
foreign import ccall "&lgammal" p'lgammal
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 107 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "llrint" c'llrint
  :: CDouble -> IO CLLong
foreign import ccall "&llrint" p'llrint
  :: FunPtr (CDouble -> IO CLLong)

{-# LINE 108 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "llrintf" c'llrintf
  :: CFloat -> IO CLLong
foreign import ccall "&llrintf" p'llrintf
  :: FunPtr (CFloat -> IO CLLong)

{-# LINE 109 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "llrintl" c'llrintl
  :: CLDouble -> IO CLLong
foreign import ccall "&llrintl" p'llrintl
  :: FunPtr (CLDouble -> IO CLLong)

{-# LINE 110 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "llround" c'llround
  :: CDouble -> IO CLLong
foreign import ccall "&llround" p'llround
  :: FunPtr (CDouble -> IO CLLong)

{-# LINE 111 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "llroundf" c'llroundf
  :: CFloat -> IO CLLong
foreign import ccall "&llroundf" p'llroundf
  :: FunPtr (CFloat -> IO CLLong)

{-# LINE 112 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "llroundl" c'llroundl
  :: CLDouble -> IO CLLong
foreign import ccall "&llroundl" p'llroundl
  :: FunPtr (CLDouble -> IO CLLong)

{-# LINE 113 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log" c'log
  :: CDouble -> IO CDouble
foreign import ccall "&log" p'log
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 114 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log10" c'log10
  :: CDouble -> IO CDouble
foreign import ccall "&log10" p'log10
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 115 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log10f" c'log10f
  :: CFloat -> IO CFloat
foreign import ccall "&log10f" p'log10f
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 116 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log10l" c'log10l
  :: CLDouble -> IO CLDouble
foreign import ccall "&log10l" p'log10l
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 117 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log1p" c'log1p
  :: CDouble -> IO CDouble
foreign import ccall "&log1p" p'log1p
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 118 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log1pf" c'log1pf
  :: CFloat -> IO CFloat
foreign import ccall "&log1pf" p'log1pf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 119 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log1pl" c'log1pl
  :: CLDouble -> IO CLDouble
foreign import ccall "&log1pl" p'log1pl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 120 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log2" c'log2
  :: CDouble -> IO CDouble
foreign import ccall "&log2" p'log2
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 121 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log2f" c'log2f
  :: CFloat -> IO CFloat
foreign import ccall "&log2f" p'log2f
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 122 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "log2l" c'log2l
  :: CLDouble -> IO CLDouble
foreign import ccall "&log2l" p'log2l
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 123 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "logb" c'logb
  :: CDouble -> IO CDouble
foreign import ccall "&logb" p'logb
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 124 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "logbf" c'logbf
  :: CFloat -> IO CFloat
foreign import ccall "&logbf" p'logbf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 125 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "logbl" c'logbl
  :: CLDouble -> IO CLDouble
foreign import ccall "&logbl" p'logbl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 126 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "logf" c'logf
  :: CFloat -> IO CFloat
foreign import ccall "&logf" p'logf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 127 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "logl" c'logl
  :: CLDouble -> IO CLDouble
foreign import ccall "&logl" p'logl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 128 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lrint" c'lrint
  :: CDouble -> IO CLong
foreign import ccall "&lrint" p'lrint
  :: FunPtr (CDouble -> IO CLong)

{-# LINE 129 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lrintf" c'lrintf
  :: CFloat -> IO CLong
foreign import ccall "&lrintf" p'lrintf
  :: FunPtr (CFloat -> IO CLong)

{-# LINE 130 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lrintl" c'lrintl
  :: CLDouble -> IO CLong
foreign import ccall "&lrintl" p'lrintl
  :: FunPtr (CLDouble -> IO CLong)

{-# LINE 131 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lround" c'lround
  :: CDouble -> IO CLong
foreign import ccall "&lround" p'lround
  :: FunPtr (CDouble -> IO CLong)

{-# LINE 132 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lroundf" c'lroundf
  :: CFloat -> IO CLong
foreign import ccall "&lroundf" p'lroundf
  :: FunPtr (CFloat -> IO CLong)

{-# LINE 133 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "lroundl" c'lroundl
  :: CLDouble -> IO CLong
foreign import ccall "&lroundl" p'lroundl
  :: FunPtr (CLDouble -> IO CLong)

{-# LINE 134 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "modf" c'modf
  :: CDouble -> Ptr CDouble -> IO CDouble
foreign import ccall "&modf" p'modf
  :: FunPtr (CDouble -> Ptr CDouble -> IO CDouble)

{-# LINE 135 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "modff" c'modff
  :: CFloat -> Ptr CFloat -> IO CFloat
foreign import ccall "&modff" p'modff
  :: FunPtr (CFloat -> Ptr CFloat -> IO CFloat)

{-# LINE 136 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "modfl" c'modfl
  :: CLDouble -> Ptr CLDouble -> IO CLDouble
foreign import ccall "&modfl" p'modfl
  :: FunPtr (CLDouble -> Ptr CLDouble -> IO CLDouble)

{-# LINE 137 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nan" c'nan
  :: CString -> IO CDouble
foreign import ccall "&nan" p'nan
  :: FunPtr (CString -> IO CDouble)

{-# LINE 138 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nanf" c'nanf
  :: CString -> IO CFloat
foreign import ccall "&nanf" p'nanf
  :: FunPtr (CString -> IO CFloat)

{-# LINE 139 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nanl" c'nanl
  :: CString -> IO CLDouble
foreign import ccall "&nanl" p'nanl
  :: FunPtr (CString -> IO CLDouble)

{-# LINE 140 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nearbyint" c'nearbyint
  :: CDouble -> IO CDouble
foreign import ccall "&nearbyint" p'nearbyint
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 141 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nearbyintf" c'nearbyintf
  :: CFloat -> IO CFloat
foreign import ccall "&nearbyintf" p'nearbyintf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 142 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nearbyintl" c'nearbyintl
  :: CLDouble -> IO CLDouble
foreign import ccall "&nearbyintl" p'nearbyintl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 143 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nextafter" c'nextafter
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&nextafter" p'nextafter
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 144 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nextafterf" c'nextafterf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&nextafterf" p'nextafterf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 145 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nextafterl" c'nextafterl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&nextafterl" p'nextafterl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 146 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nexttoward" c'nexttoward
  :: CDouble -> CLDouble -> IO CDouble
foreign import ccall "&nexttoward" p'nexttoward
  :: FunPtr (CDouble -> CLDouble -> IO CDouble)

{-# LINE 147 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nexttowardf" c'nexttowardf
  :: CFloat -> CLDouble -> IO CFloat
foreign import ccall "&nexttowardf" p'nexttowardf
  :: FunPtr (CFloat -> CLDouble -> IO CFloat)

{-# LINE 148 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "nexttowardl" c'nexttowardl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&nexttowardl" p'nexttowardl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 149 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "pow" c'pow
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&pow" p'pow
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 150 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "powf" c'powf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&powf" p'powf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 151 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "powl" c'powl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&powl" p'powl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 152 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "remainder" c'remainder
  :: CDouble -> CDouble -> IO CDouble
foreign import ccall "&remainder" p'remainder
  :: FunPtr (CDouble -> CDouble -> IO CDouble)

{-# LINE 153 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "remainderf" c'remainderf
  :: CFloat -> CFloat -> IO CFloat
foreign import ccall "&remainderf" p'remainderf
  :: FunPtr (CFloat -> CFloat -> IO CFloat)

{-# LINE 154 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "remainderl" c'remainderl
  :: CLDouble -> CLDouble -> IO CLDouble
foreign import ccall "&remainderl" p'remainderl
  :: FunPtr (CLDouble -> CLDouble -> IO CLDouble)

{-# LINE 155 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "remquo" c'remquo
  :: CDouble -> CDouble -> Ptr CInt -> IO CDouble
foreign import ccall "&remquo" p'remquo
  :: FunPtr (CDouble -> CDouble -> Ptr CInt -> IO CDouble)

{-# LINE 156 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "remquof" c'remquof
  :: CFloat -> CFloat -> Ptr CInt -> IO CFloat
foreign import ccall "&remquof" p'remquof
  :: FunPtr (CFloat -> CFloat -> Ptr CInt -> IO CFloat)

{-# LINE 157 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "remquol" c'remquol
  :: CLDouble -> CLDouble -> Ptr CInt -> IO CLDouble
foreign import ccall "&remquol" p'remquol
  :: FunPtr (CLDouble -> CLDouble -> Ptr CInt -> IO CLDouble)

{-# LINE 158 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "rint" c'rint
  :: CDouble -> IO CDouble
foreign import ccall "&rint" p'rint
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 159 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "rintf" c'rintf
  :: CFloat -> IO CFloat
foreign import ccall "&rintf" p'rintf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 160 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "rintl" c'rintl
  :: CLDouble -> IO CLDouble
foreign import ccall "&rintl" p'rintl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 161 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "round" c'round
  :: CDouble -> IO CDouble
foreign import ccall "&round" p'round
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 162 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "roundf" c'roundf
  :: CFloat -> IO CFloat
foreign import ccall "&roundf" p'roundf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 163 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "roundl" c'roundl
  :: CLDouble -> IO CLDouble
foreign import ccall "&roundl" p'roundl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 164 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "scalbln" c'scalbln
  :: CDouble -> CLong -> IO CDouble
foreign import ccall "&scalbln" p'scalbln
  :: FunPtr (CDouble -> CLong -> IO CDouble)

{-# LINE 165 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "scalblnf" c'scalblnf
  :: CFloat -> CLong -> IO CFloat
foreign import ccall "&scalblnf" p'scalblnf
  :: FunPtr (CFloat -> CLong -> IO CFloat)

{-# LINE 166 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "scalblnl" c'scalblnl
  :: CLDouble -> CLong -> IO CLDouble
foreign import ccall "&scalblnl" p'scalblnl
  :: FunPtr (CLDouble -> CLong -> IO CLDouble)

{-# LINE 167 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "scalbn" c'scalbn
  :: CDouble -> CInt -> IO CDouble
foreign import ccall "&scalbn" p'scalbn
  :: FunPtr (CDouble -> CInt -> IO CDouble)

{-# LINE 168 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "scalbnf" c'scalbnf
  :: CFloat -> CInt -> IO CFloat
foreign import ccall "&scalbnf" p'scalbnf
  :: FunPtr (CFloat -> CInt -> IO CFloat)

{-# LINE 169 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "scalbnl" c'scalbnl
  :: CLDouble -> CInt -> IO CLDouble
foreign import ccall "&scalbnl" p'scalbnl
  :: FunPtr (CLDouble -> CInt -> IO CLDouble)

{-# LINE 170 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sin" c'sin
  :: CDouble -> IO CDouble
foreign import ccall "&sin" p'sin
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 171 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sinf" c'sinf
  :: CFloat -> IO CFloat
foreign import ccall "&sinf" p'sinf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 172 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sinh" c'sinh
  :: CDouble -> IO CDouble
foreign import ccall "&sinh" p'sinh
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 173 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sinhf" c'sinhf
  :: CFloat -> IO CFloat
foreign import ccall "&sinhf" p'sinhf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 174 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sinhl" c'sinhl
  :: CLDouble -> IO CLDouble
foreign import ccall "&sinhl" p'sinhl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 175 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sinl" c'sinl
  :: CLDouble -> IO CLDouble
foreign import ccall "&sinl" p'sinl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 176 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sqrt" c'sqrt
  :: CDouble -> IO CDouble
foreign import ccall "&sqrt" p'sqrt
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 177 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sqrtf" c'sqrtf
  :: CFloat -> IO CFloat
foreign import ccall "&sqrtf" p'sqrtf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 178 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "sqrtl" c'sqrtl
  :: CLDouble -> IO CLDouble
foreign import ccall "&sqrtl" p'sqrtl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 179 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tan" c'tan
  :: CDouble -> IO CDouble
foreign import ccall "&tan" p'tan
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 180 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tanf" c'tanf
  :: CFloat -> IO CFloat
foreign import ccall "&tanf" p'tanf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 181 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tanh" c'tanh
  :: CDouble -> IO CDouble
foreign import ccall "&tanh" p'tanh
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 182 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tanhf" c'tanhf
  :: CFloat -> IO CFloat
foreign import ccall "&tanhf" p'tanhf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 183 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tanhl" c'tanhl
  :: CLDouble -> IO CLDouble
foreign import ccall "&tanhl" p'tanhl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 184 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tanl" c'tanl
  :: CLDouble -> IO CLDouble
foreign import ccall "&tanl" p'tanl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 185 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tgamma" c'tgamma
  :: CDouble -> IO CDouble
foreign import ccall "&tgamma" p'tgamma
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 186 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tgammaf" c'tgammaf
  :: CFloat -> IO CFloat
foreign import ccall "&tgammaf" p'tgammaf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 187 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "tgammal" c'tgammal
  :: CLDouble -> IO CLDouble
foreign import ccall "&tgammal" p'tgammal
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 188 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "trunc" c'trunc
  :: CDouble -> IO CDouble
foreign import ccall "&trunc" p'trunc
  :: FunPtr (CDouble -> IO CDouble)

{-# LINE 189 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "truncf" c'truncf
  :: CFloat -> IO CFloat
foreign import ccall "&truncf" p'truncf
  :: FunPtr (CFloat -> IO CFloat)

{-# LINE 190 "src/Bindings/C/Math.hsc" #-}
foreign import ccall "truncl" c'truncl
  :: CLDouble -> IO CLDouble
foreign import ccall "&truncl" p'truncl
  :: FunPtr (CLDouble -> IO CLDouble)

{-# LINE 191 "src/Bindings/C/Math.hsc" #-}