{-
 - Copyright (C) 2009-2010 Nick Bowler.
 -
 - License BSD2:  2-clause BSD license.  See LICENSE for full terms.
 - This is free software: you are free to change and redistribute it.
 - There is NO WARRANTY, to the extent permitted by law.
 -}

-- | Bindings to the standard C math library.
{-# LANGUAGE ForeignFunctionInterface #-}
module Data.Floating.CMath (
    -- * Trigonometric functions
    c_acos, c_asin, c_atan, c_atan2, c_cos, c_sin, c_tan,

    -- * Hyperbolic functions
    c_acosh, c_asinh, c_atanh, c_cosh, c_sinh, c_tanh,

    -- * Exponential functions
    c_exp, c_exp2, c_expm1, c_frexp, c_ilogb, c_ldexp, c_log, c_log10,
    c_log1p, c_log2, c_logb, c_modf, c_scalbn, c_scalbln,

    -- * Power and absolute value functions
    c_cbrt, c_fabs, c_hypot, c_pow, c_sqrt,

    -- * Remainder functions
    c_fmod, c_remainder, c_remquo,

    -- * Manipulation functions
    c_copysign, c_nan, c_nextafter,

    -- * Error and gamma functions
    c_erf, c_erfc, c_lgamma, c_tgamma,

    -- * Nearest integer functions
    c_ceil, c_floor, c_nearbyint, c_rint, c_lrint, c_llrint, c_round,
    c_lround, c_llround, c_trunc,

    -- * Maximum, minimum, and positive difference functions
    c_fdim, c_fmax, c_fmin,

    -- * Floating multiply-add
    c_fma,

    -- * Haskell wrappers
    libmDouble, libmDouble2, libmDouble3
) where

import Prelude hiding (Double, Float)

import Data.Floating.Types
import Foreign
import Foreign.C

libmDouble :: (CDouble -> CDouble) -> Double -> Double
libmDouble f a = toFloating $ f (toFloating a)

libmDouble2 :: (CDouble -> CDouble -> CDouble) -> Double -> Double -> Double
libmDouble2 f a b = toFloating $ f (toFloating a) (toFloating b)

libmDouble3 :: (CDouble -> CDouble -> CDouble -> CDouble)
    -> Double -> Double -> Double -> Double
libmDouble3 f a b c = toFloating
    $ f (toFloating a) (toFloating b) (toFloating c)

-- 7.12.4 Trigonometric functions
foreign import ccall unsafe "acos"
    c_acos :: CDouble -> CDouble
foreign import ccall unsafe "asin"
    c_asin :: CDouble -> CDouble
foreign import ccall unsafe "atan"
    c_atan :: CDouble -> CDouble
foreign import ccall unsafe "atan"
    c_atan2 :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "cos"
    c_cos :: CDouble -> CDouble
foreign import ccall unsafe "sin"
    c_sin :: CDouble -> CDouble
foreign import ccall unsafe "tan"
    c_tan :: CDouble -> CDouble

-- 7.12.5 Hyperbolic functions
foreign import ccall unsafe "acosh"
    c_acosh :: CDouble -> CDouble
foreign import ccall unsafe "asinh"
    c_asinh :: CDouble -> CDouble
foreign import ccall unsafe "atanh"
    c_atanh :: CDouble -> CDouble
foreign import ccall unsafe "cosh"
    c_cosh :: CDouble -> CDouble
foreign import ccall unsafe "sinh"
    c_sinh :: CDouble -> CDouble
foreign import ccall unsafe "tanh"
    c_tanh :: CDouble -> CDouble

-- 7.12.6 Exponential functions
foreign import ccall unsafe "exp"
    c_exp :: CDouble -> CDouble
foreign import ccall unsafe "exp2"
    c_exp2 :: CDouble -> CDouble
foreign import ccall unsafe "expm1"
    c_expm1 :: CDouble -> CDouble
foreign import ccall unsafe "frexp"
    c_frexp :: CDouble -> Ptr CInt -> IO CDouble
foreign import ccall unsafe "ilogb"
    c_ilogb :: CDouble -> CInt
foreign import ccall unsafe "ldexp"
    c_ldexp :: CDouble -> CInt -> CDouble
foreign import ccall unsafe "log"
    c_log :: CDouble -> CDouble
foreign import ccall unsafe "log10"
    c_log10 :: CDouble -> CDouble
foreign import ccall unsafe "log1p"
    c_log1p :: CDouble -> CDouble
foreign import ccall unsafe "log2"
    c_log2 :: CDouble -> CDouble
foreign import ccall unsafe "logb"
    c_logb :: CDouble -> CDouble
foreign import ccall unsafe "modf"
    c_modf :: CDouble -> Ptr CDouble -> IO CDouble
foreign import ccall unsafe "scalbn"
    c_scalbn :: CDouble -> CInt -> CDouble
foreign import ccall unsafe "scalbln"
    c_scalbln :: CDouble -> CLong -> CDouble

-- 7.12.7 Power and absolute value functions
foreign import ccall unsafe "cbrt"
    c_cbrt :: CDouble -> CDouble
foreign import ccall unsafe "fabs"
    c_fabs :: CDouble -> CDouble
foreign import ccall unsafe "hypot"
    c_hypot :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "pow"
    c_pow :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "sqrt"
    c_sqrt :: CDouble -> CDouble

-- 7.12.8 Error and gamma functions
foreign import ccall unsafe "erf"
    c_erf :: CDouble -> CDouble
foreign import ccall unsafe "erfc"
    c_erfc :: CDouble -> CDouble
foreign import ccall unsafe "lgamma"
    c_lgamma :: CDouble -> CDouble
foreign import ccall unsafe "tgamma"
    c_tgamma :: CDouble -> CDouble

-- 7.12.9 Nearest integer functions
foreign import ccall unsafe "ceil"
    c_ceil :: CDouble -> CDouble
foreign import ccall unsafe "floor"
    c_floor :: CDouble -> CDouble
foreign import ccall unsafe "nearbyint"
    c_nearbyint :: CDouble -> CDouble
foreign import ccall unsafe "rint"
    c_rint :: CDouble -> CDouble
foreign import ccall unsafe "lrint"
    c_lrint :: CDouble -> CLong
foreign import ccall unsafe "llrint"
    c_llrint :: CDouble -> CLLong
foreign import ccall unsafe "round"
    c_round :: CDouble -> CDouble
foreign import ccall unsafe "lround"
    c_lround :: CDouble -> CLong
foreign import ccall unsafe "llround"
    c_llround :: CDouble -> CLLong
foreign import ccall unsafe "trunc"
    c_trunc :: CDouble -> CDouble

-- 7.12.10 Remainder functions
foreign import ccall unsafe "fmod"
    c_fmod :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "remainder"
    c_remainder :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "remquo"
    c_remquo :: CDouble -> CDouble -> Ptr CInt -> IO CDouble

-- 7.12.11 Manipulation functions
foreign import ccall unsafe "copysign"
    c_copysign :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "nan"
    c_nan :: CString -> IO CDouble
foreign import ccall unsafe "nextafter"
    c_nextafter :: CDouble -> CDouble -> CDouble
-- no nexttoward until we have a long double type.

-- 7.12.12 Maximum, minimum, and positive difference functions
foreign import ccall unsafe "fdim"
    c_fdim :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "fmax"
    c_fmax :: CDouble -> CDouble -> CDouble
foreign import ccall unsafe "fmin"
    c_fmin :: CDouble -> CDouble -> CDouble

-- 7.12.13 Floating multiply-add
foreign import ccall unsafe "fma"
    c_fma :: CDouble -> CDouble -> CDouble -> CDouble